Skip to content

Commit

Permalink
Introduce uniformList, shuffleList and shuffleListM
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Jul 27, 2023
1 parent 632b64e commit 0ead07f
Show file tree
Hide file tree
Showing 4 changed files with 84 additions and 17 deletions.
5 changes: 5 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,11 @@
* Add default implementation for `uniformRM` using `Generics`:
[#92](https://github.com/haskell/random/pull/92)

# 1.2.2

* Add: `uniformList`
* Add: `shuffleList` and `shuffleListM`

# 1.2.1

* Fix support for ghc-9.2 [#99](https://github.com/haskell/random/pull/99)
Expand Down
33 changes: 33 additions & 0 deletions src/System/Random.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,8 @@ module System.Random
RandomGen(..)
, uniform
, uniformR
, uniformList
, shuffleList
, genByteString
, Random(..)
, Uniform
Expand Down Expand Up @@ -188,6 +190,37 @@ uniformR :: (UniformRange a, RandomGen g) => (a, a) -> g -> (a, g)
uniformR r g = runStateGen g (uniformRM r)
{-# INLINE uniformR #-}


-- | Produce a list of the supplied length with elements generated uniformly.
--
-- See `uniformListM` for a stateful counterpart.
--
-- ====__Examples__
--
-- >>> let gen = mkStdGen 2023
-- >>> import Data.Word (Word16)
-- >>> uniformList 5 gen :: ([Word16], StdGen)
-- ([56342,15850,25292,14347,13919],StdGen {unStdGen = SMGen 6446154349414395371 1920468677557965761})
--
-- @since 1.2.2
uniformList :: (Uniform a, RandomGen g) => Int -> g -> ([a], g)
uniformList r g = runStateGen g (uniformListM r)
{-# INLINE uniformList #-}


-- | Shuffle elements of a list in a random order.
--
-- ====__Examples__
--
-- >>> let gen = mkStdGen 2023
-- >>> shuffleList ['a'..'z'] gen
-- ("renlhfqmgptwksdiyavbxojzcu",StdGen {unStdGen = SMGen 9882508430712573120 1920468677557965761})
--
-- @since 1.2.2
shuffleList :: RandomGen g => [a] -> g -> ([a], g)
shuffleList xs g = runStateGen g (shuffleListM xs)
{-# INLINE shuffleList #-}

-- | Generates a 'ByteString' of the specified size using a pure pseudo-random
-- number generator. See 'uniformByteStringM' for the monadic version.
--
Expand Down
40 changes: 39 additions & 1 deletion src/System/Random/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,8 @@ module System.Random.Internal
, uniformFloatPositive01M
, uniformEnumM
, uniformEnumRM
, uniformListM
, shuffleListM

-- * Generators for sequences of pseudo-random bytes
, genShortByteStringIO
Expand All @@ -67,7 +69,7 @@ module System.Random.Internal

import Control.Arrow
import Control.DeepSeq (NFData)
import Control.Monad (when)
import Control.Monad (when, replicateM)
import Control.Monad.Cont (ContT, runContT)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.ST
Expand All @@ -78,6 +80,7 @@ import Data.Bits
import Data.ByteString.Short.Internal (ShortByteString(SBS), fromShort)
import Data.IORef (IORef, newIORef)
import Data.Int
import Data.List (sortOn)
import Data.Word
import Foreign.C.Types
import Foreign.Storable (Storable)
Expand Down Expand Up @@ -541,6 +544,41 @@ runStateGenST_ g action = runST $ runStateGenT_ g action
{-# INLINE runStateGenST_ #-}


-- | Generates a list of pseudo-random values.
--
-- ====__Examples__
--
-- >>> import System.Random.Stateful
-- >>> let pureGen = mkStdGen 137
-- >>> g <- newIOGenM pureGen
-- >>> uniformListM 10 g :: IO [Bool]
-- [True,True,True,True,False,True,True,False,False,False]
--
-- @since 1.2.0
uniformListM :: (StatefulGen g m, Uniform a) => Int -> g -> m [a]
uniformListM n gen = replicateM n (uniformM gen)
{-# INLINE uniformListM #-}

-- | Shuffle elements of a list in a random order.
--
-- ====__Examples__
--
-- >>> import System.Random.Stateful
-- >>> let pureGen = mkStdGen 2023
-- >>> g <- newIOGenM pureGen
-- >>> shuffleListM ['a'..'z'] g :: IO String
-- "renlhfqmgptwksdiyavbxojzcu"
--
-- @since 1.2.2
shuffleListM :: StatefulGen g m => [a] -> g -> m [a]
shuffleListM xs gen = do
is <- uniformListM n gen
pure $ map snd $ sortOn fst $ zip (is :: [Int]) xs
where
!n = length xs
{-# INLINE shuffleListM #-}


-- | The standard pseudo-random number generator.
newtype StdGen = StdGen { unStdGen :: SM.SMGen }
deriving (Show, RandomGen, NFData)
Expand Down
23 changes: 7 additions & 16 deletions src/System/Random/Stateful.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,10 +76,13 @@ module System.Random.Stateful
-- * Pseudo-random values of various types
-- $uniform
, Uniform(..)
, uniformListM
, uniformViaFiniteM
, UniformRange(..)

-- * Lists
, uniformListM
, shuffleListM

-- * Generators for sequences of pseudo-random bytes
, genShortByteStringIO
, genShortByteStringST
Expand All @@ -104,7 +107,6 @@ module System.Random.Stateful
) where

import Control.DeepSeq
import Control.Monad (replicateM)
import Control.Monad.IO.Class
import Control.Monad.ST
import GHC.Conc.Sync (STM, TVar, newTVar, newTVarIO, readTVar, writeTVar)
Expand Down Expand Up @@ -146,6 +148,7 @@ import System.Random.Internal
-- range @[1, 6]@ in a 'StatefulGen' context; given a /monadic/ pseudo-random
-- number generator, you can run this probabilistic computation as follows:
--
-- >>> import Control.Monad (replicateM)
-- >>> :{
-- let rollsM :: StatefulGen g m => Int -> g -> m [Word]
-- rollsM n = replicateM n . uniformRM (1, 6)
Expand Down Expand Up @@ -274,20 +277,6 @@ withMutableGen_ :: FrozenGen f m => f -> (MutableGen f m -> m a) -> m a
withMutableGen_ fg action = fst <$> withMutableGen fg action


-- | Generates a list of pseudo-random values.
--
-- ====__Examples__
--
-- >>> import System.Random.Stateful
-- >>> let pureGen = mkStdGen 137
-- >>> g <- newIOGenM pureGen
-- >>> uniformListM 10 g :: IO [Bool]
-- [True,True,True,True,False,True,True,False,False,False]
--
-- @since 1.2.0
uniformListM :: (StatefulGen g m, Uniform a) => Int -> g -> m [a]
uniformListM n gen = replicateM n (uniformM gen)

-- | Generates a pseudo-random value using monadic interface and `Random` instance.
--
-- ====__Examples__
Expand Down Expand Up @@ -355,6 +344,7 @@ newAtomicGenM = fmap AtomicGenM . liftIO . newIORef
-- | Global mutable standard pseudo-random number generator. This is the same
-- generator that was historically used by `randomIO` and `randomRIO` functions.
--
-- >>> import Control.Monad (replicateM)
-- >>> replicateM 10 (uniformRM ('a', 'z') globalStdGen)
-- "tdzxhyfvgr"
--
Expand Down Expand Up @@ -776,6 +766,7 @@ applyTGen f (TGenM tvar) = do
-- produces a short list with random even integers.
--
-- >>> import Data.Int (Int8)
-- >>> import Control.Monad (replicateM)
-- >>> :{
-- myCustomRandomList :: FrozenGen f m => f -> m [Int8]
-- myCustomRandomList f =
Expand Down

0 comments on commit 0ead07f

Please sign in to comment.