Skip to content

Commit 81161a2

Browse files
committed
Deprecate RandomGenM in favor of a more powerful FrozenGen
* Addition of `modifyM` totally removes the need for `RandomGenM`, because every frozen generator that is a wrapper around `RandomGen` also derives an instance for `RandomGen` * Add `splitMutableM` and `splitFrozenM`
1 parent dcb5bc2 commit 81161a2

File tree

3 files changed

+68
-7
lines changed

3 files changed

+68
-7
lines changed

CHANGELOG.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,9 @@
11
# 1.3.0
22

3+
* Add `modifyM` to the `FrozenGen` type class
4+
* Add `splitFrozenM` and `splitMutableM`
5+
* Switch `randomM` and `randomRM` to use `FrozenGen` instead of `RandomGenM`
6+
* Deprecate `RandomGenM` in favor of a more powerful `FrozenGen`
37
* Add `isInRange` to `UniformRange`: [#78](https://github.com/haskell/random/pull/78)
48
* Add default implementation for `uniformRM` using `Generics`:
59
[#92](https://github.com/haskell/random/pull/92)

src/System/Random/Internal.hs

Lines changed: 28 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,8 @@ module System.Random.Internal
3030
RandomGen(..)
3131
, StatefulGen(..)
3232
, FrozenGen(..)
33+
, splitFrozenM
34+
, splitMutableM
3335

3436
-- ** Standard pseudo-random number generator
3537
, StdGen(..)
@@ -67,7 +69,7 @@ module System.Random.Internal
6769

6870
import Control.Arrow
6971
import Control.DeepSeq (NFData)
70-
import Control.Monad (when)
72+
import Control.Monad (when, (>=>))
7173
import Control.Monad.Cont (ContT, runContT)
7274
import Control.Monad.IO.Class (MonadIO(..))
7375
import Control.Monad.ST
@@ -289,6 +291,9 @@ class Monad m => StatefulGen g m where
289291
-- | This class is designed for stateful pseudo-random number generators that
290292
-- can be saved as and restored from an immutable data type.
291293
--
294+
-- It also works great on working with mutable generators that are based on a pure
295+
-- geenrator that has an `RandomGen` instance.
296+
--
292297
-- @since 1.2.0
293298
class StatefulGen (MutableGen f m) m => FrozenGen f m where
294299
-- | Represents the state of the pseudo-random number generator for use with
@@ -305,6 +310,26 @@ class StatefulGen (MutableGen f m) m => FrozenGen f m where
305310
-- @since 1.2.0
306311
thawGen :: f -> m (MutableGen f m)
307312

313+
-- | Apply a pure function to the frozen generator.
314+
--
315+
-- @since 1.3.0
316+
modifyM :: MutableGen f m -> (f -> (a, f)) -> m a
317+
318+
319+
-- | Splits a pseudo-random number generator into two. Overwrites the mutable
320+
-- wrapper with one of the resulting generators and returns the other.
321+
--
322+
-- @since 1.3.0
323+
splitFrozenM :: (RandomGen f, FrozenGen f m) => MutableGen f m -> m f
324+
splitFrozenM = flip modifyM split
325+
326+
-- | Splits a pseudo-random number generator into two. Overwrites the mutable
327+
-- wrapper with one of the resulting generators and returns the other.
328+
--
329+
-- @since 1.3.0
330+
splitMutableM :: (RandomGen f, FrozenGen f m) => MutableGen f m -> m (MutableGen f m)
331+
splitMutableM = splitFrozenM >=> thawGen
332+
308333

309334
data MBA = MBA (MutableByteArray# RealWorld)
310335

@@ -452,6 +477,8 @@ instance (RandomGen g, MonadState g m) => FrozenGen (StateGen g) m where
452477
type MutableGen (StateGen g) m = StateGenM g
453478
freezeGen _ = fmap StateGen get
454479
thawGen (StateGen g) = StateGenM <$ put g
480+
modifyM _ f = state (coerce f)
481+
{-# INLINE modifyM #-}
455482

456483
-- | Splits a pseudo-random number generator into two. Updates the state with
457484
-- one of the resulting generators and returns the other.

src/System/Random/Stateful.hs

Lines changed: 36 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE FunctionalDependencies #-}
44
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
55
{-# LANGUAGE RankNTypes #-}
6+
{-# LANGUAGE ScopedTypeVariables #-}
67
{-# LANGUAGE Trustworthy #-}
78
{-# LANGUAGE TypeFamilies #-}
89
{-# LANGUAGE UndecidableInstances #-}
@@ -29,11 +30,15 @@ module System.Random.Stateful
2930
-- $interfaces
3031
, StatefulGen(..)
3132
, FrozenGen(..)
32-
, RandomGenM(..)
3333
, withMutableGen
3434
, withMutableGen_
3535
, randomM
3636
, randomRM
37+
, splitFrozenM
38+
, splitMutableM
39+
40+
-- ** Deprecated
41+
, RandomGenM(..)
3742
, splitGenM
3843

3944
-- * Monadic adapters for pure pseudo-random number generators #monadicadapters#
@@ -216,13 +221,16 @@ import System.Random.Internal
216221
-- @since 1.2.0
217222
class (RandomGen r, StatefulGen g m) => RandomGenM g r m | g -> r where
218223
applyRandomGenM :: (r -> (a, r)) -> g -> m a
224+
{-# DEPRECATED applyRandomGenM "In favor of `modifyM`" #-}
225+
{-# DEPRECATED RandomGenM "In favor of `FrozenGen`" #-}
219226

220227
-- | Splits a pseudo-random number generator into two. Overwrites the mutable
221228
-- wrapper with one of the resulting generators and returns the other.
222229
--
223230
-- @since 1.2.0
224231
splitGenM :: RandomGenM g r m => g -> m r
225232
splitGenM = applyRandomGenM split
233+
{-# DEPRECATED splitGenM "In favor of `splitM`" #-}
226234

227235
instance (RandomGen r, MonadIO m) => RandomGenM (IOGenM r) r m where
228236
applyRandomGenM = applyIOGen
@@ -301,8 +309,8 @@ uniformListM n gen = replicateM n (uniformM gen)
301309
-- 0.6268211351114487
302310
--
303311
-- @since 1.2.0
304-
randomM :: (Random a, RandomGenM g r m) => g -> m a
305-
randomM = applyRandomGenM random
312+
randomM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => MutableGen g m -> m a
313+
randomM = flip modifyM random
306314

307315
-- | Generates a pseudo-random value using monadic interface and `Random` instance.
308316
--
@@ -321,8 +329,8 @@ randomM = applyRandomGenM random
321329
-- 2
322330
--
323331
-- @since 1.2.0
324-
randomRM :: (Random a, RandomGenM g r m) => (a, a) -> g -> m a
325-
randomRM r = applyRandomGenM (randomR r)
332+
randomRM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => (a, a) -> MutableGen g m -> m a
333+
randomRM r = flip modifyM (randomR r)
326334

327335
-- | Wraps an 'IORef' that holds a pure pseudo-random number generator. All
328336
-- operations are performed atomically.
@@ -379,6 +387,11 @@ instance (RandomGen g, MonadIO m) => FrozenGen (AtomicGen g) m where
379387
type MutableGen (AtomicGen g) m = AtomicGenM g
380388
freezeGen = fmap AtomicGen . liftIO . readIORef . unAtomicGenM
381389
thawGen (AtomicGen g) = newAtomicGenM g
390+
modifyM (AtomicGenM ioRef) f =
391+
liftIO $ atomicModifyIORef' ioRef $ \g ->
392+
case f (AtomicGen g) of
393+
(a, AtomicGen g') -> (g', a)
394+
{-# INLINE modifyM #-}
382395

383396
-- | Atomically applies a pure operation to the wrapped pseudo-random number
384397
-- generator.
@@ -454,7 +467,12 @@ instance (RandomGen g, MonadIO m) => FrozenGen (IOGen g) m where
454467
type MutableGen (IOGen g) m = IOGenM g
455468
freezeGen = fmap IOGen . liftIO . readIORef . unIOGenM
456469
thawGen (IOGen g) = newIOGenM g
457-
470+
modifyM (IOGenM ref) f = liftIO $ do
471+
g <- readIORef ref
472+
let (a, IOGen g') = f (IOGen g)
473+
g' `seq` writeIORef ref g'
474+
pure a
475+
{-# INLINE modifyM #-}
458476

459477
-- | Applies a pure operation to the wrapped pseudo-random number generator.
460478
--
@@ -514,6 +532,12 @@ instance RandomGen g => FrozenGen (STGen g) (ST s) where
514532
type MutableGen (STGen g) (ST s) = STGenM g s
515533
freezeGen = fmap STGen . readSTRef . unSTGenM
516534
thawGen (STGen g) = newSTGenM g
535+
modifyM (STGenM ref) f = do
536+
g <- readSTRef ref
537+
let (a, STGen g') = f (STGen g)
538+
g' `seq` writeSTRef ref g'
539+
pure a
540+
{-# INLINE modifyM #-}
517541

518542

519543
-- | Applies a pure operation to the wrapped pseudo-random number generator.
@@ -609,6 +633,12 @@ instance RandomGen g => FrozenGen (TGen g) STM where
609633
type MutableGen (TGen g) STM = TGenM g
610634
freezeGen = fmap TGen . readTVar . unTGenM
611635
thawGen (TGen g) = newTGenM g
636+
modifyM (TGenM ref) f = do
637+
g <- readTVar ref
638+
let (a, TGen g') = f (TGen g)
639+
g' `seq` writeTVar ref g'
640+
pure a
641+
{-# INLINE modifyM #-}
612642

613643

614644
-- | Applies a pure operation to the wrapped pseudo-random number generator.

0 commit comments

Comments
 (0)