Skip to content

Commit

Permalink
Merge pull request #176 from haskell/lehins/use-consistent-naming
Browse files Browse the repository at this point in the history
Use consistent naming
  • Loading branch information
lehins authored Jan 6, 2025
2 parents 404fa39 + c7ddd91 commit 2df7069
Show file tree
Hide file tree
Showing 9 changed files with 131 additions and 79 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/ci.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
8 changes: 6 additions & 2 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,13 +20,17 @@
`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
* Deprecate `System.Random.Stateful.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
* 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`
* 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`.
Expand Down
2 changes: 1 addition & 1 deletion bench/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 ->
Expand Down
5 changes: 5 additions & 0 deletions scripts/doctest.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
#!/usr/bin/env bash

set -euo pipefail

cabal repl --build-depends=unliftio --with-compiler=doctest --repl-options='-w -Wdefault'
80 changes: 74 additions & 6 deletions src/System/Random.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE Trustworthy #-}

-- |
Expand Down Expand Up @@ -49,7 +51,9 @@ module System.Random
-- ** Bytes
, uniformByteArray
, uniformByteString
, uniformShortByteString
, uniformFillMutableByteArray
-- *** Deprecated
, genByteString
, genShortByteString

Expand Down Expand Up @@ -88,15 +92,18 @@ module System.Random
import Control.Arrow
import Control.Monad.IO.Class
import Control.Monad.State.Strict
import Control.Monad.ST (ST)
import Data.Array.Byte (ByteArray(..), MutableByteArray(..))
import Data.ByteString (ByteString)
import Data.ByteString.Short.Internal (ShortByteString(..))
import Data.Int
import Data.IORef
import Data.Word
import Foreign.C.Types
import GHC.Exts
import System.Random.Array (shuffleListST)
import System.Random.Array (getSizeOfMutableByteArray, 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

Expand Down Expand Up @@ -316,16 +323,77 @@ 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 (unpack)
-- >>> 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 #-}

-- | 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 #-}

-- | 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
Expand Down
75 changes: 19 additions & 56 deletions src/System/Random/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,12 +71,9 @@ module System.Random.Internal
, scaleFloating

-- * Generators for sequences of pseudo-random bytes
, uniformByteStringM
, uniformShortByteStringM
, uniformByteArray
, uniformFillMutableByteArray
, uniformByteString
, genByteArrayST
, fillByteArrayST
, genShortByteStringIO
, genShortByteStringST
, defaultUnsafeFillMutableByteArrayT
Expand Down Expand Up @@ -105,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
Expand Down Expand Up @@ -228,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
Expand Down Expand Up @@ -269,6 +272,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
Expand Down Expand Up @@ -496,43 +500,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 #-}

-- | 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 #-}
{-# INLINE fillByteArrayST #-}

defaultUnsafeFillMutableByteArrayT ::
(Monad (t (ST s)), MonadTrans t)
Expand Down Expand Up @@ -592,22 +572,13 @@ 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
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 #-}
{-# 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.
--
Expand All @@ -618,6 +589,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.
Expand All @@ -627,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.
--
Expand Down Expand Up @@ -819,9 +781,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.
--
Expand Down
18 changes: 14 additions & 4 deletions src/System/Random/Stateful.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,7 @@ module System.Random.Stateful

-- * Helper functions for createing instances
-- ** Sequences of bytes
, genByteArrayST
, fillByteArrayST
, genShortByteStringIO
, genShortByteStringST
, defaultUnsafeUniformFillMutableByteArray
Expand Down Expand Up @@ -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
import System.Random.Array (shuffleListM)
import System.Random hiding (uniformShortByteString)
import System.Random.Array (shuffleListM, shortByteStringToByteString)
import System.Random.Internal
#if __GLASGOW_HASKELL__ >= 808
import GHC.IORef (atomicModifyIORef2Lazy)
Expand Down Expand Up @@ -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.
--
Expand Down Expand Up @@ -933,7 +943,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)
Expand Down
13 changes: 7 additions & 6 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -129,12 +130,12 @@ byteStringSpec :: TestTree
byteStringSpec =
testGroup
"ByteString"
[ SC.testProperty "genShortByteString" $
seededWithLen $ \n g -> SBS.length (fst (genShortByteString n g)) == n
, SC.testProperty "genByteString" $
[ SC.testProperty "uniformShortByteString" $
seededWithLen $ \n g -> SBS.length (fst (uniformShortByteString n g)) == n
, 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 (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]
forM_ [0 .. length bs - 1] $ \ n -> do
Expand Down
Loading

0 comments on commit 2df7069

Please sign in to comment.