Skip to content

Commit

Permalink
Deprecate RandomGenM in favor of a more powerful FrozenGen
Browse files Browse the repository at this point in the history
* 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`
  • Loading branch information
lehins committed Oct 29, 2023
1 parent e182019 commit 618b5e4
Show file tree
Hide file tree
Showing 3 changed files with 68 additions and 7 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
@@ -1,5 +1,9 @@
# 1.3.0

* Add `modifyM` to the `FrozenGen` type class
* Add `splitFrozenM` and `splitMutableM`
* Switch `randomM` and `randomRM` to use `FrozenGen` instead of `RandomGenM`
* Deprecate `RandomGenM` in favor of a more powerful `FrozenGen`
* Add `isInRange` to `UniformRange`: [#78](https://github.com/haskell/random/pull/78)
* Add default implementation for `uniformRM` using `Generics`:
[#92](https://github.com/haskell/random/pull/92)
Expand Down
29 changes: 28 additions & 1 deletion src/System/Random/Internal.hs
Expand Up @@ -30,6 +30,8 @@ module System.Random.Internal
RandomGen(..)
, StatefulGen(..)
, FrozenGen(..)
, splitFrozenM
, splitMutableM

-- ** Standard pseudo-random number generator
, StdGen(..)
Expand Down Expand Up @@ -67,7 +69,7 @@ module System.Random.Internal

import Control.Arrow
import Control.DeepSeq (NFData)
import Control.Monad (when)
import Control.Monad (when, (>=>))
import Control.Monad.Cont (ContT, runContT)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.ST
Expand Down Expand Up @@ -289,6 +291,9 @@ class Monad m => StatefulGen g m where
-- | This class is designed for stateful pseudo-random number generators that
-- can be saved as and restored from an immutable data type.
--
-- It also works great on working with mutable generators that are based on a pure
-- geenrator that has an `RandomGen` instance.
--
-- @since 1.2.0
class StatefulGen (MutableGen f m) m => FrozenGen f m where
-- | Represents the state of the pseudo-random number generator for use with
Expand All @@ -305,6 +310,26 @@ class StatefulGen (MutableGen f m) m => FrozenGen f m where
-- @since 1.2.0
thawGen :: f -> m (MutableGen f m)

-- | Apply a pure function to the frozen generator.
--
-- @since 1.3.0
modifyM :: MutableGen f m -> (f -> (a, f)) -> m a


-- | Splits a pseudo-random number generator into two. Overwrites the mutable
-- wrapper with one of the resulting generators and returns the other.
--
-- @since 1.3.0
splitFrozenM :: (RandomGen f, FrozenGen f m) => MutableGen f m -> m f
splitFrozenM = flip modifyM split

-- | Splits a pseudo-random number generator into two. Overwrites the mutable
-- wrapper with one of the resulting generators and returns the other.
--
-- @since 1.3.0
splitMutableM :: (RandomGen f, FrozenGen f m) => MutableGen f m -> m (MutableGen f m)
splitMutableM = splitFrozenM >=> thawGen


data MBA = MBA (MutableByteArray# RealWorld)

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

-- | Splits a pseudo-random number generator into two. Updates the state with
-- one of the resulting generators and returns the other.
Expand Down
42 changes: 36 additions & 6 deletions src/System/Random/Stateful.hs
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
Expand All @@ -29,11 +30,15 @@ module System.Random.Stateful
-- $interfaces
, StatefulGen(..)
, FrozenGen(..)
, RandomGenM(..)
, withMutableGen
, withMutableGen_
, randomM
, randomRM
, splitFrozenM
, splitMutableM

-- ** Deprecated
, RandomGenM(..)
, splitGenM

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

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

instance (RandomGen r, MonadIO m) => RandomGenM (IOGenM r) r m where
applyRandomGenM = applyIOGen
Expand Down Expand Up @@ -301,8 +309,8 @@ uniformListM n gen = replicateM n (uniformM gen)
-- 0.6268211351114487
--
-- @since 1.2.0
randomM :: (Random a, RandomGenM g r m) => g -> m a
randomM = applyRandomGenM random
randomM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => MutableGen g m -> m a
randomM = flip modifyM random

-- | Generates a pseudo-random value using monadic interface and `Random` instance.
--
Expand All @@ -321,8 +329,8 @@ randomM = applyRandomGenM random
-- 2
--
-- @since 1.2.0
randomRM :: (Random a, RandomGenM g r m) => (a, a) -> g -> m a
randomRM r = applyRandomGenM (randomR r)
randomRM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => (a, a) -> MutableGen g m -> m a
randomRM r = flip modifyM (randomR r)

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

-- | Atomically applies a pure operation to the wrapped pseudo-random number
-- generator.
Expand Down Expand Up @@ -454,7 +467,12 @@ instance (RandomGen g, MonadIO m) => FrozenGen (IOGen g) m where
type MutableGen (IOGen g) m = IOGenM g
freezeGen = fmap IOGen . liftIO . readIORef . unIOGenM
thawGen (IOGen g) = newIOGenM g

modifyM (IOGenM ref) f = liftIO $ do
g <- readIORef ref
let (a, IOGen g') = f (IOGen g)
g' `seq` writeIORef ref g'
pure a
{-# INLINE modifyM #-}

-- | Applies a pure operation to the wrapped pseudo-random number generator.
--
Expand Down Expand Up @@ -514,6 +532,12 @@ instance RandomGen g => FrozenGen (STGen g) (ST s) where
type MutableGen (STGen g) (ST s) = STGenM g s
freezeGen = fmap STGen . readSTRef . unSTGenM
thawGen (STGen g) = newSTGenM g
modifyM (STGenM ref) f = do
g <- readSTRef ref
let (a, STGen g') = f (STGen g)
g' `seq` writeSTRef ref g'
pure a
{-# INLINE modifyM #-}


-- | Applies a pure operation to the wrapped pseudo-random number generator.
Expand Down Expand Up @@ -609,6 +633,12 @@ instance RandomGen g => FrozenGen (TGen g) STM where
type MutableGen (TGen g) STM = TGenM g
freezeGen = fmap TGen . readTVar . unTGenM
thawGen (TGen g) = newTGenM g
modifyM (TGenM ref) f = do
g <- readTVar ref
let (a, TGen g') = f (TGen g)
g' `seq` writeTVar ref g'
pure a
{-# INLINE modifyM #-}


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

0 comments on commit 618b5e4

Please sign in to comment.