
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}