Skip to content

Commit

Permalink
Add seedSizeProxy and a doctest example
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Dec 28, 2024
1 parent 673fdc3 commit 04a7b56
Show file tree
Hide file tree
Showing 3 changed files with 52 additions and 9 deletions.
2 changes: 1 addition & 1 deletion CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

* Improve floating point value generation and avoid degenerate cases: [#172](https://github.com/haskell/random/pull/172)
* Add `Uniform` instance for `Maybe` and `Either`: [#167](https://github.com/haskell/random/pull/167)
* Add `Seed`, `SeedGen`, `seedSize`, `mkSeed` and `unSeed`:
* Add `Seed`, `SeedGen`, `seedSize`, `seedSizeProxy`, `mkSeed` and `unSeed`:
[#162](https://github.com/haskell/random/pull/162)
* Add `SplitGen` and `splitGen`: [#160](https://github.com/haskell/random/pull/160)
* Add `unifromShuffleList` and `unifromShuffleListM`: [#140](https://github.com/haskell/random/pull/140)
Expand Down
9 changes: 8 additions & 1 deletion src/System/Random/Seed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ module System.Random.Seed
, -- ** Seed
Seed
, seedSize
, seedSizeProxy
, mkSeed
, unSeed
, mkSeedFromByteString
Expand Down Expand Up @@ -207,6 +208,12 @@ instance SeedGen g => Uniform (Seed g) where
seedSize :: forall g. SeedGen g => Int
seedSize = fromIntegral $ natVal (Proxy :: Proxy (SeedSize g))

-- | Just like `seedSize`, except it accepts a proxy as an argument.
--
-- @since 1.3.0
seedSizeProxy :: forall proxy g. SeedGen g => proxy g -> Int
seedSizeProxy _px = seedSize @g

-- | Construct a `Seed` from a `ByteArray` of expected length. Whenever `ByteArray` does
-- not match the `SeedSize` specified by the pseudo-random generator, this function will
-- `F.fail`.
Expand Down Expand Up @@ -240,7 +247,7 @@ withSeed seed f = runIdentity (withSeedM seed (pure . f))

-- | Same as `withSeed`, except it is useful with monadic computation and frozen generators.
--
-- See `System.Random.Stateful.withMutableSeedGen` for a helper that also handles seeds
-- See `System.Random.Stateful.withSeedMutableGen` for a helper that also handles seeds
-- for mutable pseduo-random number generators.
--
-- @since 1.3.0
Expand Down
50 changes: 43 additions & 7 deletions src/System/Random/Stateful.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,8 @@ module System.Random.Stateful
, ThawedGen(..)
, withMutableGen
, withMutableGen_
, withMutableSeedGen
, withMutableSeedGen_
, withSeedMutableGen
, withSeedMutableGen_
, randomM
, randomRM
, splitGenM
Expand Down Expand Up @@ -320,17 +320,53 @@ withMutableGen_ fg action = thawGen fg >>= action

-- | Just like `withMutableGen`, except uses a `Seed` instead of a frozen generator.
--
-- ====__Examples__
--
-- Here is good example of how `withSeedMutableGen` can be used with `withSeedFile`, which uses a locally stored seed.
--
-- First we define a @reportSeed@ function that will print the contents of a seed file as a list of bytes:
--
-- >>> import Data.ByteString as BS (readFile, writeFile, unpack)
-- >>> :seti -XOverloadedStrings
-- >>> let reportSeed fp = print . ("Seed: " <>) . show . BS.unpack =<< BS.readFile fp
--
-- Given a file path, write an `StdGen` seed into the file:
--
-- >>> :seti -XFlexibleContexts -XScopedTypeVariables
-- >>> let writeInitSeed fp = BS.writeFile fp (unSeedToByteString (unSeedGen (mkStdGen 2025)))
--
-- Apply a `StatefulGen` monadic action that uses @`IOGen` `StdGen`@, restored from the seed in the given path:
--
-- >>> let withMutableSeedFile fp action = withSeedFile fp (\(seed :: Seed (IOGen StdGen)) -> withSeedMutableGen seed action)
--
-- Given a path and an action initialize the seed file and apply the action using that seed:
--
-- >>> let withInitSeedFile fp action = writeInitSeed fp *> reportSeed fp *> withMutableSeedFile fp action <* reportSeed fp
--
-- For the sake of example we will use a temporary directory for storing the seed. Here we
-- report the contents of the seed file before and after we shuffle a list:
--
-- >>> import UnliftIO.Temporary (withSystemTempDirectory)
-- >>> withSystemTempDirectory "random" (\fp -> withInitSeedFile (fp ++ "/seed.bin") (uniformShuffleListM [1..10]))
-- "Seed: [183,178,143,77,132,163,109,14,157,105,82,99,148,82,109,173]"
-- "Seed: [60,105,117,203,187,138,69,39,157,105,82,99,148,82,109,173]"
-- [7,5,4,3,1,8,10,6,9,2]
--
-- @since 1.3.0
withMutableSeedGen :: (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m (a, Seed g)
withMutableSeedGen seed f = withSeedM seed (`withMutableGen` f)
withSeedMutableGen :: (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m (a, Seed g)
withSeedMutableGen seed f = withSeedM seed (`withMutableGen` f)

-- | Just like `withMutableSeedGen`, except it doesn't return the final generator, only
-- | Just like `withSeedMutableGen`, except it doesn't return the final generator, only
-- the resulting value. This is slightly more efficient, since it doesn't incur overhead
-- from freezeing the mutable generator
--
-- @since 1.3.0
withMutableSeedGen_ :: (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m a
withMutableSeedGen_ seed = withMutableGen_ (seedGen seed)
withSeedMutableGen_ :: (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m a
withSeedMutableGen_ seed = withMutableGen_ (seedGen seed)

withSeedFileMutableGen_ :: forall g m. (SeedGen g, ThawedGen g m, MonadIO m) => Seed g -> (MutableGen g m -> m a) -> m a
withSeedFileMutableGen_ seed =
withMutableGen_ (seedGen seed)


-- | Generates a pseudo-random value using monadic interface and `Random` instance.
Expand Down

0 comments on commit 04a7b56

Please sign in to comment.