From 25c4371a0bce6c2fc6e16aba0cf81a8a15f9ca66 Mon Sep 17 00:00:00 2001 From: Alexey Kuleshevich Date: Sun, 5 Jan 2025 18:34:59 -0700 Subject: [PATCH 1/7] Add a `doctest.sh` script for ease of local testing --- .github/workflows/ci.yaml | 2 +- scripts/doctest.sh | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) create mode 100755 scripts/doctest.sh diff --git a/.github/workflows/ci.yaml b/.github/workflows/ci.yaml index c8d99a6d..20f2e4c2 100644 --- a/.github/workflows/ci.yaml +++ b/.github/workflows/ci.yaml @@ -96,7 +96,7 @@ jobs: - name: Doctest run: | cabal install doctest --ignore-project --overwrite-policy=always - cabal repl --build-depends=unliftio --with-compiler=doctest --repl-options='-w -Wdefault' + ./scripts/doctest.sh build-stack: name: CI-stack diff --git a/scripts/doctest.sh b/scripts/doctest.sh new file mode 100755 index 00000000..53e1cfda --- /dev/null +++ b/scripts/doctest.sh @@ -0,0 +1,5 @@ +#!/usr/bin/env bash + +set -euo pipefail + +cabal repl --build-depends=unliftio --with-compiler=doctest --repl-options='-w -Wdefault' From c242d1378aff4bc65ae55fd101bcc81146f13326 Mon Sep 17 00:00:00 2001 From: Alexey Kuleshevich Date: Sun, 5 Jan 2025 18:36:32 -0700 Subject: [PATCH 2/7] Deprecate `genByteString` in favor of `uniformByteString` --- CHANGELOG.md | 1 + bench/Main.hs | 2 +- src/System/Random.hs | 28 +++++++++++++++++++++++----- src/System/Random/Internal.hs | 11 ----------- test/Spec.hs | 6 +++--- 5 files changed, 28 insertions(+), 20 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 6fffa1d9..7c8ca6ae 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -20,6 +20,7 @@ `defaultUnsafeUniformFillMutableByteArray` that makes implementation for most instances easier. * Add `uniformByteArray`, `uniformByteString` and `uniformFillMutableByteArray` + * Deprecate `genByteString` in favor of `uniformByteString` * Add `uniformByteArrayM` to `StatefulGen` * Add `uniformByteStringM` and `uniformShortByteStringM` * Deprecate `uniformShortByteString` in favor of `uniformShortByteStringM` for diff --git a/bench/Main.hs b/bench/Main.hs index ea2a91c2..b17b89f8 100644 --- a/bench/Main.hs +++ b/bench/Main.hs @@ -294,7 +294,7 @@ main = do , env getStdGen $ \gen -> bench "uniformByteArray 100MB" $ nf (\n -> uniformByteArray False n gen) sz100MiB , env getStdGen $ \gen -> - bench "genByteString 100MB" $ nf (`genByteString` gen) sz100MiB + bench "uniformByteString 100MB" $ nf (`uniformByteString` gen) sz100MiB ] ] , env (pure [0 :: Integer .. 200000]) $ \xs -> diff --git a/src/System/Random.hs b/src/System/Random.hs index e7efe7d2..cf1aa772 100644 --- a/src/System/Random.hs +++ b/src/System/Random.hs @@ -94,7 +94,7 @@ import Data.IORef import Data.Word import Foreign.C.Types import GHC.Exts -import System.Random.Array (shuffleListST) +import System.Random.Array (shortByteStringToByteString, shuffleListST) import System.Random.GFinite (Finite) import System.Random.Internal import System.Random.Seed @@ -316,16 +316,34 @@ uniformShuffleList xs g = -- >>> import System.Random -- >>> import Data.ByteString -- >>> let pureGen = mkStdGen 137 +-- >>> :seti -Wno-deprecations -- >>> unpack . fst . genByteString 10 $ pureGen -- [51,123,251,37,49,167,90,109,1,4] -- --- /Note/ - This function is equivalet to `uniformByteString` and will be deprecated in --- the next major release. --- -- @since 1.2.0 genByteString :: RandomGen g => Int -> g -> (ByteString, g) -genByteString n g = runStateGenST g (uniformByteStringM n) +genByteString = uniformByteString {-# INLINE genByteString #-} +{-# DEPRECATED genByteString "In favor of `uniformByteString`" #-} + +-- | Generates a 'ByteString' of the specified size using a pure pseudo-random +-- number generator. See 'uniformByteStringM' for the monadic version. +-- +-- ====__Examples__ +-- +-- >>> import System.Random +-- >>> import Data.ByteString +-- >>> let pureGen = mkStdGen 137 +-- >>> unpack . fst $ uniformByteString 10 pureGen +-- [51,123,251,37,49,167,90,109,1,4] +-- +-- @since 1.3.0 +uniformByteString :: RandomGen g => Int -> g -> (ByteString, g) +uniformByteString n g = + case uniformByteArray True n g of + (byteArray, g') -> + (shortByteStringToByteString $ byteArrayToShortByteString byteArray, g') +{-# INLINE uniformByteString #-} -- | The class of types for which random values can be generated. Most -- instances of `Random` will produce values that are uniformly distributed on the full diff --git a/src/System/Random/Internal.hs b/src/System/Random/Internal.hs index 02136e68..7dd3381d 100644 --- a/src/System/Random/Internal.hs +++ b/src/System/Random/Internal.hs @@ -75,7 +75,6 @@ module System.Random.Internal , uniformShortByteStringM , uniformByteArray , uniformFillMutableByteArray - , uniformByteString , genByteArrayST , genShortByteStringIO , genShortByteStringST @@ -592,16 +591,6 @@ defaultUnsafeUniformFillMutableByteArray mba i0 n g = {-# INLINE defaultUnsafeUniformFillMutableByteArray #-} --- | Generates a pseudo-random 'ByteString' of the specified size. --- --- @since 1.3.0 -uniformByteString :: RandomGen g => Int -> g -> (ByteString, g) -uniformByteString n g = - case uniformByteArray True n g of - (byteArray, g') -> - (shortByteStringToByteString $ byteArrayToShortByteString byteArray, g') -{-# INLINE uniformByteString #-} - -- | Same as 'genShortByteStringIO', but runs in 'ST'. -- -- @since 1.2.0 diff --git a/test/Spec.hs b/test/Spec.hs index de79ca73..99aba06e 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -131,10 +131,10 @@ byteStringSpec = "ByteString" [ SC.testProperty "genShortByteString" $ seededWithLen $ \n g -> SBS.length (fst (genShortByteString n g)) == n - , SC.testProperty "genByteString" $ + , SC.testProperty "uniformByteString" $ seededWithLen $ \n g -> - SBS.toShort (fst (genByteString n g)) == fst (genShortByteString n g) - , testCase "genByteString/ShortByteString consistency" $ do + SBS.toShort (fst (uniformByteString n g)) == fst (genShortByteString n g) + , testCase "uniformByteString/ShortByteString consistency" $ do let g = mkStdGen 2021 bs = [78,232,117,189,13,237,63,84,228,82,19,36,191,5,128,192] :: [Word8] forM_ [0 .. length bs - 1] $ \ n -> do From 249207916d93dc06b86563bb0cb0c3e35a3682d0 Mon Sep 17 00:00:00 2001 From: Alexey Kuleshevich Date: Sun, 5 Jan 2025 19:03:44 -0700 Subject: [PATCH 3/7] Rename `genByteArrayST` to `fillByteArrayST` --- CHANGELOG.md | 2 +- src/System/Random/Internal.hs | 12 ++++++------ src/System/Random/Stateful.hs | 4 ++-- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 7c8ca6ae..697fa299 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -26,7 +26,7 @@ * Deprecate `uniformShortByteString` in favor of `uniformShortByteStringM` for consistent naming and a future plan of removing it from `StatefulGen` type class - * Expose a helper function `genByteArrayST`, that can be used for + * Expose a helper function `fillByteArrayST`, that can be used for defining implementation for `uniformByteArrayM` * Improve `FrozenGen` interface: [#149](https://github.com/haskell/random/pull/149) * Move `thawGen` from `FreezeGen` into the new `ThawGen` type class. Fixes an issue with diff --git a/src/System/Random/Internal.hs b/src/System/Random/Internal.hs index 7dd3381d..a0c02c4e 100644 --- a/src/System/Random/Internal.hs +++ b/src/System/Random/Internal.hs @@ -75,7 +75,7 @@ module System.Random.Internal , uniformShortByteStringM , uniformByteArray , uniformFillMutableByteArray - , genByteArrayST + , fillByteArrayST , genShortByteStringIO , genShortByteStringST , defaultUnsafeFillMutableByteArrayT @@ -495,19 +495,19 @@ uniformByteArray isPinned n0 g = pure (ba, g') {-# INLINE uniformByteArray #-} --- | Using an `ST` action that generates 8 bytes at a type fill in a new `ByteArray` in +-- | Using an `ST` action that generates 8 bytes at a time fill in a new `ByteArray` in -- architecture agnostic manner. -- -- @since 1.3.0 -genByteArrayST :: Bool -> Int -> ST s Word64 -> ST s ByteArray -genByteArrayST isPinned n0 action = do +fillByteArrayST :: Bool -> Int -> ST s Word64 -> ST s ByteArray +fillByteArrayST isPinned n0 action = do let !n = max 0 n0 mba <- if isPinned then newPinnedMutableByteArray n else newMutableByteArray n runIdentityT $ defaultUnsafeFillMutableByteArrayT mba 0 n (lift action) freezeMutableByteArray mba -{-# INLINE genByteArrayST #-} +{-# INLINE fillByteArrayST #-} -- | Fill in a slice of a mutable byte array with randomly generated bytes. This function -- does not fail, instead it adjust the offset and number of bytes to generate into a valid @@ -595,7 +595,7 @@ defaultUnsafeUniformFillMutableByteArray mba i0 n g = -- -- @since 1.2.0 genShortByteStringST :: Int -> ST s Word64 -> ST s ShortByteString -genShortByteStringST n0 action = byteArrayToShortByteString <$> genByteArrayST False n0 action +genShortByteStringST n0 action = byteArrayToShortByteString <$> fillByteArrayST False n0 action {-# INLINE genShortByteStringST #-} -- | Efficiently fills in a new `ShortByteString` in a platform independent manner. diff --git a/src/System/Random/Stateful.hs b/src/System/Random/Stateful.hs index 17eb69e0..a83a00cb 100644 --- a/src/System/Random/Stateful.hs +++ b/src/System/Random/Stateful.hs @@ -108,7 +108,7 @@ module System.Random.Stateful -- * Helper functions for createing instances -- ** Sequences of bytes - , genByteArrayST + , fillByteArrayST , genShortByteStringIO , genShortByteStringST , defaultUnsafeUniformFillMutableByteArray @@ -933,7 +933,7 @@ applyTGen f (TGenM tvar) = do -- > uniformWord16 = MWC.uniform -- > uniformWord32 = MWC.uniform -- > uniformWord64 = MWC.uniform --- > uniformByteArrayM isPinned n g = stToPrim (genByteArrayST isPinned n (MWC.uniform g)) +-- > uniformByteArrayM isPinned n g = stToPrim (fillByteArrayST isPinned n (MWC.uniform g)) -- -- > instance PrimMonad m => FrozenGen MWC.Seed m where -- > type MutableGen MWC.Seed m = MWC.Gen (PrimState m) From 8a0f6b7fe1f357647bc3f3bbf61055601a654803 Mon Sep 17 00:00:00 2001 From: Alexey Kuleshevich Date: Sun, 5 Jan 2025 19:10:38 -0700 Subject: [PATCH 4/7] Deprecate `genShortByteStringST` and `genShortByteStringIO` in favor of `fillByteArrayST` --- CHANGELOG.md | 1 + src/System/Random/Internal.hs | 2 ++ 2 files changed, 3 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 697fa299..9ef76db5 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -28,6 +28,7 @@ type class * Expose a helper function `fillByteArrayST`, that can be used for defining implementation for `uniformByteArrayM` + * Deprecate `genShortByteStringST` and `genShortByteStringIO` in favor of `fillByteArrayST` * Improve `FrozenGen` interface: [#149](https://github.com/haskell/random/pull/149) * Move `thawGen` from `FreezeGen` into the new `ThawGen` type class. Fixes an issue with an unlawful instance of `StateGen` for `FreezeGen`. diff --git a/src/System/Random/Internal.hs b/src/System/Random/Internal.hs index a0c02c4e..1b75c5d0 100644 --- a/src/System/Random/Internal.hs +++ b/src/System/Random/Internal.hs @@ -597,6 +597,7 @@ defaultUnsafeUniformFillMutableByteArray mba i0 n g = genShortByteStringST :: Int -> ST s Word64 -> ST s ShortByteString genShortByteStringST n0 action = byteArrayToShortByteString <$> fillByteArrayST False n0 action {-# INLINE genShortByteStringST #-} +{-# DEPRECATED genShortByteStringST "In favor of `fillByteArrayST`, since `uniformShortByteString`, which it was used for, was also deprecated" #-} -- | Efficiently fills in a new `ShortByteString` in a platform independent manner. -- @@ -607,6 +608,7 @@ genShortByteStringIO :: -> IO ShortByteString genShortByteStringIO n ioAction = stToIO $ genShortByteStringST n (ioToST ioAction) {-# INLINE genShortByteStringIO #-} +{-# DEPRECATED genShortByteStringIO "In favor of `fillByteArrayST`" #-} -- | @uniformShortByteString n g@ generates a 'ShortByteString' of length @n@ -- filled with pseudo-random bytes. From ae69ab3961aa18ee7053bd21b56336511f814c2d Mon Sep 17 00:00:00 2001 From: Alexey Kuleshevich Date: Sun, 5 Jan 2025 19:45:52 -0700 Subject: [PATCH 5/7] Add a pure `System.Random.uniformShortByteString` generating function. * Deprecate `genShortByteString` in favor of `System.Random.uniformShortByteString` --- CHANGELOG.md | 4 +++- src/System/Random.hs | 28 ++++++++++++++++++++++++++-- src/System/Random/Internal.hs | 1 + src/System/Random/Stateful.hs | 2 +- test/Spec.hs | 9 +++++---- test/Spec/Stateful.hs | 7 ++++--- 6 files changed, 40 insertions(+), 11 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 9ef76db5..ae29a9f7 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -23,9 +23,11 @@ * Deprecate `genByteString` in favor of `uniformByteString` * Add `uniformByteArrayM` to `StatefulGen` * Add `uniformByteStringM` and `uniformShortByteStringM` - * Deprecate `uniformShortByteString` in favor of `uniformShortByteStringM` for + * Deprecate `System.Random.Stateful.uniformShortByteString` in favor of `uniformShortByteStringM` for consistent naming and a future plan of removing it from `StatefulGen` type class + * Add a pure `System.Random.uniformShortByteString` generating function. + * Deprecate `genShortByteString` in favor of `System.Random.uniformShortByteString` * Expose a helper function `fillByteArrayST`, that can be used for defining implementation for `uniformByteArrayM` * Deprecate `genShortByteStringST` and `genShortByteStringIO` in favor of `fillByteArrayST` diff --git a/src/System/Random.hs b/src/System/Random.hs index cf1aa772..f9f09acf 100644 --- a/src/System/Random.hs +++ b/src/System/Random.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DefaultSignatures #-} +{-# LANGUAGE MagicHash #-} {-# LANGUAGE Trustworthy #-} -- | @@ -49,7 +50,9 @@ module System.Random -- ** Bytes , uniformByteArray , uniformByteString + , uniformShortByteString , uniformFillMutableByteArray + -- *** Deprecated , genByteString , genShortByteString @@ -88,7 +91,9 @@ module System.Random import Control.Arrow import Control.Monad.IO.Class import Control.Monad.State.Strict +import Data.Array.Byte (ByteArray(..)) import Data.ByteString (ByteString) +import Data.ByteString.Short.Internal (ShortByteString(..)) import Data.Int import Data.IORef import Data.Word @@ -96,7 +101,7 @@ import Foreign.C.Types import GHC.Exts import System.Random.Array (shortByteStringToByteString, shuffleListST) import System.Random.GFinite (Finite) -import System.Random.Internal +import System.Random.Internal hiding (uniformShortByteString) import System.Random.Seed import qualified System.Random.SplitMix as SM @@ -332,7 +337,7 @@ genByteString = uniformByteString -- ====__Examples__ -- -- >>> import System.Random --- >>> import Data.ByteString +-- >>> import Data.ByteString (unpack) -- >>> let pureGen = mkStdGen 137 -- >>> unpack . fst $ uniformByteString 10 pureGen -- [51,123,251,37,49,167,90,109,1,4] @@ -345,6 +350,25 @@ uniformByteString n g = (shortByteStringToByteString $ byteArrayToShortByteString byteArray, g') {-# INLINE uniformByteString #-} +-- | Same as @`uniformByteArray` `False`@, but for `ShortByteString`. +-- +-- Returns a 'ShortByteString' of length @n@ filled with pseudo-random bytes. +-- +-- ====__Examples__ +-- +-- >>> import System.Random +-- >>> import Data.ByteString.Short (unpack) +-- >>> let pureGen = mkStdGen 137 +-- >>> unpack . fst $ uniformShortByteString 10 pureGen +-- [51,123,251,37,49,167,90,109,1,4] +-- +-- @since 1.3.0 +uniformShortByteString :: RandomGen g => Int -> g -> (ShortByteString, g) +uniformShortByteString n g = + case uniformByteArray False n g of + (ByteArray ba#, g') -> (SBS ba#, g') +{-# INLINE uniformShortByteString #-} + -- | The class of types for which random values can be generated. Most -- instances of `Random` will produce values that are uniformly distributed on the full -- range, but for those types without a well-defined "full range" some sensible default diff --git a/src/System/Random/Internal.hs b/src/System/Random/Internal.hs index 1b75c5d0..c1094fdd 100644 --- a/src/System/Random/Internal.hs +++ b/src/System/Random/Internal.hs @@ -268,6 +268,7 @@ class RandomGen g where default split :: SplitGen g => g -> (g, g) split = splitGen +{-# DEPRECATED genShortByteString "In favor of `System.Random.uniformShortByteString`" #-} {-# DEPRECATED split "In favor of `splitGen`" #-} -- | Pseudo-random generators that can be split into two separate and independent diff --git a/src/System/Random/Stateful.hs b/src/System/Random/Stateful.hs index a83a00cb..ce954794 100644 --- a/src/System/Random/Stateful.hs +++ b/src/System/Random/Stateful.hs @@ -145,7 +145,7 @@ import Data.Coerce import Data.IORef import Data.STRef import Foreign.Storable -import System.Random +import System.Random hiding (uniformShortByteString) import System.Random.Array (shuffleListM) import System.Random.Internal #if __GLASGOW_HASKELL__ >= 808 diff --git a/test/Spec.hs b/test/Spec.hs index 99aba06e..808f1150 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -24,7 +24,8 @@ import Foreign.C.Types import GHC.Generics import GHC.Exts (fromList) import Numeric.Natural (Natural) -import System.Random.Stateful +import System.Random (uniformShortByteString) +import System.Random.Stateful hiding (uniformShortByteString) import System.Random.Internal (newMutableByteArray, freezeMutableByteArray, writeWord8) import Test.SmallCheck.Series as SC import Test.Tasty @@ -129,11 +130,11 @@ byteStringSpec :: TestTree byteStringSpec = testGroup "ByteString" - [ SC.testProperty "genShortByteString" $ - seededWithLen $ \n g -> SBS.length (fst (genShortByteString n g)) == n + [ SC.testProperty "uniformShortByteString" $ + seededWithLen $ \n g -> SBS.length (fst (uniformShortByteString n g)) == n , SC.testProperty "uniformByteString" $ seededWithLen $ \n g -> - SBS.toShort (fst (uniformByteString n g)) == fst (genShortByteString n g) + SBS.toShort (fst (uniformByteString n g)) == fst (uniformShortByteString n g) , testCase "uniformByteString/ShortByteString consistency" $ do let g = mkStdGen 2021 bs = [78,232,117,189,13,237,63,84,228,82,19,36,191,5,128,192] :: [Word8] diff --git a/test/Spec/Stateful.hs b/test/Spec/Stateful.hs index e575f117..454b66e9 100644 --- a/test/Spec/Stateful.hs +++ b/test/Spec/Stateful.hs @@ -11,7 +11,8 @@ import Control.Monad import Control.Monad.ST import Data.Proxy import Data.Typeable -import System.Random.Stateful +import System.Random (uniformShortByteString) +import System.Random.Stateful hiding (uniformShortByteString) import Test.SmallCheck.Series import Test.Tasty import Test.Tasty.SmallCheck as SC @@ -155,12 +156,12 @@ frozenGenSpecFor fromStdGen toStdGen runStatefulGen = , testProperty "uniformWord64R/genWord64R" $ forAll $ \w64 -> matchRandomGenSpec (uniformWord64R w64) (genWord64R w64) fromStdGen toStdGen runStatefulGen - , testProperty "uniformShortByteStringM/genShortByteString" $ + , testProperty "uniformShortByteStringM/uniformShortByteString" $ forAll $ \(NonNegative n') -> let n = n' `mod` 100000 -- Ensure it is not too big in matchRandomGenSpec (uniformShortByteStringM n) - (genShortByteString n) + (uniformShortByteString n) fromStdGen toStdGen runStatefulGen From 389c88c9eca1e47db002777202ebfcebbc25289b Mon Sep 17 00:00:00 2001 From: Alexey Kuleshevich Date: Sun, 5 Jan 2025 19:55:28 -0700 Subject: [PATCH 6/7] Simplify implementation of `mkStdGen` --- src/System/Random/Internal.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/System/Random/Internal.hs b/src/System/Random/Internal.hs index c1094fdd..b31595af 100644 --- a/src/System/Random/Internal.hs +++ b/src/System/Random/Internal.hs @@ -811,9 +811,10 @@ instance SplitGen SM32.SMGen where splitGen = SM32.splitSMGen {-# INLINE splitGen #-} --- | Constructs a 'StdGen' deterministically. +-- | Constructs a 'StdGen' deterministically from an `Int` seed. See `mkStdGen64` for a `Word64` +-- variant that is architecture agnostic. mkStdGen :: Int -> StdGen -mkStdGen = StdGen . SM.mkSMGen . fromIntegral +mkStdGen = mkStdGen64 . fromIntegral -- | Constructs a 'StdGen' deterministically from a `Word64` seed. -- From c7ddd919119d76bb57d550c40ecd66f0d4c92f7e Mon Sep 17 00:00:00 2001 From: Alexey Kuleshevich Date: Sun, 5 Jan 2025 20:16:25 -0700 Subject: [PATCH 7/7] Move things around and add some haddock --- src/System/Random.hs | 30 ++++++++++++++++++++++-- src/System/Random/Internal.hs | 44 ++++++----------------------------- src/System/Random/Stateful.hs | 12 +++++++++- 3 files changed, 46 insertions(+), 40 deletions(-) diff --git a/src/System/Random.hs b/src/System/Random.hs index f9f09acf..c9f474e0 100644 --- a/src/System/Random.hs +++ b/src/System/Random.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE MagicHash #-} @@ -91,7 +92,8 @@ module System.Random import Control.Arrow import Control.Monad.IO.Class import Control.Monad.State.Strict -import Data.Array.Byte (ByteArray(..)) +import Control.Monad.ST (ST) +import Data.Array.Byte (ByteArray(..), MutableByteArray(..)) import Data.ByteString (ByteString) import Data.ByteString.Short.Internal (ShortByteString(..)) import Data.Int @@ -99,7 +101,7 @@ import Data.IORef import Data.Word import Foreign.C.Types import GHC.Exts -import System.Random.Array (shortByteStringToByteString, shuffleListST) +import System.Random.Array (getSizeOfMutableByteArray, shortByteStringToByteString, shuffleListST) import System.Random.GFinite (Finite) import System.Random.Internal hiding (uniformShortByteString) import System.Random.Seed @@ -369,6 +371,30 @@ uniformShortByteString n g = (ByteArray ba#, g') -> (SBS ba#, g') {-# INLINE uniformShortByteString #-} +-- | Fill in a slice of a mutable byte array with randomly generated bytes. This function +-- does not fail, instead it clamps the offset and number of bytes to generate into a valid +-- range. +-- +-- @since 1.3.0 +uniformFillMutableByteArray :: + RandomGen g + => MutableByteArray s + -- ^ Mutable array to fill with random bytes + -> Int + -- ^ Offset into a mutable array from the beginning in number of bytes. Offset will be + -- clamped into the range between 0 and the total size of the mutable array + -> Int + -- ^ Number of randomly generated bytes to write into the array. This number will be + -- clamped between 0 and the total size of the array without the offset. + -> g + -> ST s g +uniformFillMutableByteArray mba i0 n g = do + !sz <- getSizeOfMutableByteArray mba + let !offset = max 0 (min sz i0) + !numBytes = min (sz - offset) (max 0 n) + unsafeUniformFillMutableByteArray mba offset numBytes g +{-# INLINE uniformFillMutableByteArray #-} + -- | The class of types for which random values can be generated. Most -- instances of `Random` will produce values that are uniformly distributed on the full -- range, but for those types without a well-defined "full range" some sensible default diff --git a/src/System/Random/Internal.hs b/src/System/Random/Internal.hs index b31595af..f6967cd9 100644 --- a/src/System/Random/Internal.hs +++ b/src/System/Random/Internal.hs @@ -71,10 +71,8 @@ module System.Random.Internal , scaleFloating -- * Generators for sequences of pseudo-random bytes - , uniformByteStringM , uniformShortByteStringM , uniformByteArray - , uniformFillMutableByteArray , fillByteArrayST , genShortByteStringIO , genShortByteStringST @@ -104,7 +102,6 @@ import Control.Monad.Trans (lift, MonadTrans) import Control.Monad.Trans.Identity (IdentityT (runIdentityT)) import Data.Array.Byte (ByteArray(..), MutableByteArray(..)) import Data.Bits -import Data.ByteString (ByteString) import Data.ByteString.Short.Internal (ShortByteString(SBS)) import Data.IORef (IORef, newIORef) import Data.Int @@ -227,6 +224,13 @@ class RandomGen g where (ByteArray ba#, g') -> (SBS ba#, g') {-# INLINE genShortByteString #-} + -- | Fill in the supplied `MutableByteArray` with uniformly generated random bytes. This function + -- is unsafe because it is not required to do any bounds checking. For a safe variant use + -- `System.Random.Sateful.uniformFillMutableByteArrayM` instead. + -- + -- Default type class implementation uses `defaultUnsafeUniformFillMutableByteArray`. + -- + -- @since 1.3.0 unsafeUniformFillMutableByteArray :: MutableByteArray s -- ^ Mutable array to fill with random bytes @@ -510,30 +514,6 @@ fillByteArrayST isPinned n0 action = do freezeMutableByteArray mba {-# INLINE fillByteArrayST #-} --- | Fill in a slice of a mutable byte array with randomly generated bytes. This function --- does not fail, instead it adjust the offset and number of bytes to generate into a valid --- range. --- --- @since 1.3.0 -uniformFillMutableByteArray :: - RandomGen g - => MutableByteArray s - -- ^ Mutable array to fill with random bytes - -> Int - -- ^ Offset into a mutable array from the beginning in number of bytes. Offset will be - -- clamped into the range between 0 and the total size of the mutable array - -> Int - -- ^ Number of randomly generated bytes to write into the array. This number will be - -- clamped between 0 and the total size of the array without the offset. - -> g - -> ST s g -uniformFillMutableByteArray mba i0 n g = do - !sz <- getSizeOfMutableByteArray mba - let !offset = max 0 (min sz i0) - !numBytes = min (sz - offset) (max 0 n) - unsafeUniformFillMutableByteArray mba offset numBytes g -{-# INLINE uniformFillMutableByteArray #-} - defaultUnsafeFillMutableByteArrayT :: (Monad (t (ST s)), MonadTrans t) => MutableByteArray s @@ -619,16 +599,6 @@ uniformShortByteStringM :: StatefulGen g m => Int -> g -> m ShortByteString uniformShortByteStringM n g = byteArrayToShortByteString <$> uniformByteArrayM False n g {-# INLINE uniformShortByteStringM #-} --- | Generates a pseudo-random 'ByteString' of the specified size. --- --- @since 1.2.0 -uniformByteStringM :: StatefulGen g m => Int -> g -> m ByteString -uniformByteStringM n g = - shortByteStringToByteString . byteArrayToShortByteString - <$> uniformByteArrayM True n g -{-# INLINE uniformByteStringM #-} - - -- | Opaque data type that carries the type of a pure pseudo-random number -- generator. -- diff --git a/src/System/Random/Stateful.hs b/src/System/Random/Stateful.hs index ce954794..546e97ca 100644 --- a/src/System/Random/Stateful.hs +++ b/src/System/Random/Stateful.hs @@ -141,12 +141,13 @@ import Control.Monad.IO.Class import Control.Monad.ST import GHC.Conc.Sync (STM, TVar, newTVar, newTVarIO, readTVar, writeTVar) import Control.Monad.State.Strict (MonadState, state) +import Data.ByteString (ByteString) import Data.Coerce import Data.IORef import Data.STRef import Foreign.Storable import System.Random hiding (uniformShortByteString) -import System.Random.Array (shuffleListM) +import System.Random.Array (shuffleListM, shortByteStringToByteString) import System.Random.Internal #if __GLASGOW_HASKELL__ >= 808 import GHC.IORef (atomicModifyIORef2Lazy) @@ -407,6 +408,15 @@ randomRM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => (a, a) -> Mu randomRM r = flip modifyGen (randomR r) {-# INLINE randomRM #-} +-- | Generates a pseudo-random 'ByteString' of the specified size. +-- +-- @since 1.2.0 +uniformByteStringM :: StatefulGen g m => Int -> g -> m ByteString +uniformByteStringM n g = + shortByteStringToByteString . byteArrayToShortByteString + <$> uniformByteArrayM True n g +{-# INLINE uniformByteStringM #-} + -- | Wraps an 'IORef' that holds a pure pseudo-random number generator. All -- operations are performed atomically. --