
I would like to point out the importance of Cale Gibbard's MonadRandom, beyond what is currently mentioned on its wiki page: http://www.haskell.org/haskellwiki/New_monads/MonadRandom This monad makes it possible to write functions that use randomness without having to specify in advance whether the source of randomness will be a pure pseudorandom number generator, as in System.Random, or physical randomness via the IO monad, such as your operating system's source of physical randomness, or random.org, or a hardware random generator. Before use of MonadRandom becomes widespread - and I think it ought to - I would like to suggest a change to the interface. (I mentioned this once to Cale on #haskell, but I didn't say what change I meant.) Currently, the members of the MonadRandom class mimic the members of the Random class in System.Random. I think it would be better if instead they mimicked the members of RandomGen. Like this: \begin{code} class (Monad m) => MonadRandom m where nextR :: m Int splitR :: m (m ()) rangeR :: m (Int, Int) getR :: (forall g . RandomGen g => g -> a) -> m a \end{code} The extra function getR provides access not only to the member functions of Random, but to any function that generates random variables of any type. You would use getR random, getR $ randomR (a, b), etc. instead of getRandom, getRandomR (a, b), etc. Provide a default method for getR as follows: \begin{code} getR f = do r <- nextR (lo, hi) <- rangeR return $ f $ TrivialGen r lo hi data TrivialGen = TrivialGen Int Int Int instance RandomGen TrivialGen where next (TrivialGen r _ _) = r genRange (TrivialGen _ lo hi) = (lo, hi) split _ = undefined \end{code} We would use the default method of getR for MonadRandom instances of things like DevRandom, DevURandom, RandomDotOrg, etc. For the Rand and RandT instances we provide explicit methods: \begin{code} -- For RandT: getR f = RandT $ gets f --For Rand: getR =Rand $ getR f \end{code} I think this is better for several reasons: o We anyway need getR for general random variables o We could lose precision getting other random variables via getRandom in the case where genRange /= (minBound, maxBound) o I think it is a better semantic fit Regards, Yitz

I wrote:
Cale Gibbard's MonadRandom... I would like to suggest a change to the interface... class (Monad m) => MonadRandom m where nextR :: m Int splitR :: m (m ()) rangeR :: m (Int, Int) getR :: (forall g . RandomGen g => g -> a) -> m a
I see that I have inadvertently done two things differently than Cale with regard to split: Cale used a different type, and he put it into a separate monad. The separate monad idea is a very good one. My type is bit more general than Cale's, and it emphasizes the amusing fact that split is a kind of inverse to monadic join. (Actually, a section.) But Cale's type looks more convenient to use. I am modifying my proposal accordingly on both points. Below are the new versions of the classes. Any comments? Thanks, Yitz \begin{code} class Monad m => MonadRandom m where nextR :: m Int rangeR :: m (Int, Int) getR :: (forall g . RandomGen g => g -> a) -> m a -- Minimum complete definition: nextR and rangeR getR f = do r <- nextR (lo, hi) <- rangeR return $ f $ TrivalGen r lo hi class MonadRandom m => MonadRandomSplittable m where splitR :: m a -> m (m a) splitRandom :: m a -> m a -- Use the following default method definitions only -- when splitting is a trivial operation, such as for -- hardware-based random generators. splitR = return splitRandom = id instance Monad m => MonadRandomSplittable (RandT m) where splitR x = RandT (StateT split) >>= return . (>> x) . RandT . put splitRandom x = RandT (StateT split) >>= lift . evalRandT x instance MonadRandomSplittable Rand where splitR = liftState split >>= return . liftState . put splitRandom x = Rand (State split) >>= return . evalRand x \end{code}

The splittable idea isn't mine, it looks like perhaps Remi Turk did it.
One thing which I'd recommend is including getRandom, getRandomR as
implemented in terms of getR and the ordinary random operations,
simply because they're the two most common uses, it's probably worth
it to define them separately. Also, getRandoms and getRandomRs would
still be convenient to have in the library, and should do appropriate
splitting of the generator.
- Cale
On 06/02/07, Yitzchak Gale
I wrote:
Cale Gibbard's MonadRandom... I would like to suggest a change to the interface... class (Monad m) => MonadRandom m where nextR :: m Int splitR :: m (m ()) rangeR :: m (Int, Int) getR :: (forall g . RandomGen g => g -> a) -> m a
I see that I have inadvertently done two things differently than Cale with regard to split: Cale used a different type, and he put it into a separate monad.
The separate monad idea is a very good one.
My type is bit more general than Cale's, and it emphasizes the amusing fact that split is a kind of inverse to monadic join. (Actually, a section.) But Cale's type looks more convenient to use.
I am modifying my proposal accordingly on both points.
Below are the new versions of the classes. Any comments?
Thanks, Yitz
\begin{code}
class Monad m => MonadRandom m where nextR :: m Int rangeR :: m (Int, Int) getR :: (forall g . RandomGen g => g -> a) -> m a -- Minimum complete definition: nextR and rangeR getR f = do r <- nextR (lo, hi) <- rangeR return $ f $ TrivalGen r lo hi
class MonadRandom m => MonadRandomSplittable m where splitR :: m a -> m (m a) splitRandom :: m a -> m a -- Use the following default method definitions only -- when splitting is a trivial operation, such as for -- hardware-based random generators. splitR = return splitRandom = id
instance Monad m => MonadRandomSplittable (RandT m) where splitR x = RandT (StateT split) >>= return . (>> x) . RandT . put splitRandom x = RandT (StateT split) >>= lift . evalRandT x
instance MonadRandomSplittable Rand where splitR = liftState split >>= return . liftState . put splitRandom x = Rand (State split) >>= return . evalRand x
\end{code}

OK, thanks! Regards, Yitz Cale Gibbard wrote:
The splittable idea isn't mine, it looks like perhaps Remi Turk did it.
One thing which I'd recommend is including getRandom, getRandomR as implemented in terms of getR and the ordinary random operations, simply because they're the two most common uses, it's probably worth it to define them separately. Also, getRandoms and getRandomRs would still be convenient to have in the library, and should do appropriate splitting of the generator.
participants (2)
-
Cale Gibbard
-
Yitzchak Gale