Difference between revisions of "New monads/MonadRandomSplittable"

From HaskellWiki
Jump to navigation Jump to search
m (fix a MonadRandomSplittable "law")
 
(5 intermediate revisions by 2 users not shown)
Line 15: Line 15:
 
newtype Rand g a = Rand { unRand :: RandomT g Identity a }
 
newtype Rand g a = Rand { unRand :: RandomT g Identity a }
 
deriving (Functor, Monad, MonadRandom, MonadRandomSplittable)
 
deriving (Functor, Monad, MonadRandom, MonadRandomSplittable)
  +
</haskell>
  +
  +
Some potentially useful functions
  +
<haskell>
  +
splitRandoms :: MonadRandomSplittable m => [m a] -> m [a]
  +
splitRandoms [] = splitRandom $ return []
  +
splitRandoms (x:xs) = splitRandom $ liftM2 (:) x (splitRandoms xs)
  +
  +
getRandoms :: (MonadRandomSplittable m, Random a) => m [a]
  +
getRandoms = liftM2 (:) getRandom (splitRandom getRandoms)
  +
  +
getRandomRs :: (MonadRandomSplittable m, Random a) => (a, a) -> m [a]
  +
getRandomRs b = liftM2 (:) (getRandomR b) (splitRandom (getRandomRs b))
 
</haskell>
 
</haskell>
   
Line 45: Line 58:
 
== Laws ==
 
== Laws ==
   
It is not clear to me exactly what [[Monad laws|laws]] <hask>splitRandom</hask> should satisfy, besides monadic variations of the "split laws" from the Haskell Library Report [http://haskell.org/onlinereport/random.html]
+
It is not clear to me exactly what [[Monad laws|laws]] <hask>splitRandom</hask> should satisfy, besides monadic variations of the "split laws" from the [http://haskell.org/onlinereport/random.html Haskell Library Report]
   
 
For all terminating <hask>ma</hask> and <hask>mb</hask>, it should hold that
 
For all terminating <hask>ma</hask> and <hask>mb</hask>, it should hold that
 
<haskell>
 
<haskell>
liftM3 (\a _ c -> (a,c)) getRandom ma getRandom === liftM3 (\a _ c -> (a,c)) getRandom mb getRandom
+
liftM3 (\a _ c -> (a,c)) getRandom (splitRandom ma) getRandom
 
</haskell>
 
</haskell>
  +
and
  +
<haskell>
  +
liftM3 (\a _ c -> (a,c)) getRandom (splitRandom mb) getRandom
  +
</haskell>
  +
return the same pair.
   
 
For [[monad transformer]]s, it would also be nice if
 
For [[monad transformer]]s, it would also be nice if
Line 80: Line 98:
 
== Why? ==
 
== Why? ==
 
In <hask>replicateM 100 (splitRandom expensiveAction)</hask> There are no RNG-dependencies between the different expensiveActions, so they may be computed in parallel.
 
In <hask>replicateM 100 (splitRandom expensiveAction)</hask> There are no RNG-dependencies between the different expensiveActions, so they may be computed in parallel.
  +
  +
The following constructs a tree of infinite depth and width:
  +
<haskell>
  +
import Data.Tree
  +
import Data.List
  +
  +
makeRandomTree = liftM2 Node (getRandomR ('a','z')) (splitRandoms $ repeat makeRandomTree)
  +
</haskell>
  +
By removing the RNG-dependencies, infinite random data structures can be constructed lazily.
  +
  +
And for completeness the non-monadic version:
  +
<haskell>
  +
randomTree g = Node a (map randomTree gs)
  +
where
  +
(a, g') = randomR ('a','z') g
  +
gs = unfoldr (Just . split) g'
  +
</haskell>
  +
Note that the monadic version does more split operations, so yields different results.

Latest revision as of 22:10, 27 November 2007


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)

Some potentially useful functions

splitRandoms        :: MonadRandomSplittable m => [m a] -> m [a]
splitRandoms []     = splitRandom $ return []
splitRandoms (x:xs) = splitRandom $ liftM2 (:) x (splitRandoms xs)

getRandoms      :: (MonadRandomSplittable m, Random a) => m [a]
getRandoms      = liftM2 (:) getRandom (splitRandom getRandoms)

getRandomRs     :: (MonadRandomSplittable m, Random a) => (a, a) -> m [a]
getRandomRs b   = liftM2 (:) (getRandomR b) (splitRandom (getRandomRs b))

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 (splitRandom ma) getRandom

and

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

return the same pair.

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.

The following constructs a tree of infinite depth and width:

import Data.Tree
import Data.List

makeRandomTree  = liftM2 Node (getRandomR ('a','z')) (splitRandoms $ repeat makeRandomTree)

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

And for completeness the non-monadic version:

randomTree g    = Node a (map randomTree gs)
    where
        (a, g') = randomR ('a','z') g
        gs      = unfoldr (Just . split) g'

Note that the monadic version does more split operations, so yields different results.