Skip to content

Commit

Permalink
Move things around and add some haddock
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Jan 6, 2025
1 parent 389c88c commit c7ddd91
Show file tree
Hide file tree
Showing 3 changed files with 46 additions and 40 deletions.
30 changes: 28 additions & 2 deletions src/System/Random.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE MagicHash #-}
Expand Down Expand Up @@ -91,15 +92,16 @@ 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
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
Expand Down Expand Up @@ -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
Expand Down
44 changes: 7 additions & 37 deletions src/System/Random/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,10 +71,8 @@ module System.Random.Internal
, scaleFloating

-- * Generators for sequences of pseudo-random bytes
, uniformByteStringM
, uniformShortByteStringM
, uniformByteArray
, uniformFillMutableByteArray
, fillByteArrayST
, genShortByteStringIO
, genShortByteStringST
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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.
--
Expand Down
12 changes: 11 additions & 1 deletion src/System/Random/Stateful.hs
Original file line number Diff line number Diff line change
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 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)
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

0 comments on commit c7ddd91

Please sign in to comment.