Bad Semantics

System.Random.Stateful Explained

Introduction

Writing algorithms with an aspect of randomness is a pretty common thing a programmer might need to do.

Haskell, being pure, makes this a little bit of a head-scratching exercise: a function with different outputs for the same input would violate break referential transparency.

System.Random from the random package provides the tools for modelling a pseudorandom process as a pure function that takes and returns a value representing the state of a random number generator, but if we're honest, piping around these immutable states isn't nearly as convenient as making an impure random(1,10) call in an imperative language.

How do we get a similar levels of convenience? We need a stateful monad. The trouble is that Haskell throws a plethora of stateful monad options at us and it's difficult to know what monad to write your randomized algorithm in.

The System.Random.Stateful module is a relatively recent addition to the random package that offers to allow you to avoid choosing and enable you to write randomized algorithms that work in many different stateful monads.

Unfortunately System.Random.Stateful seems to be a pretty hard library to wrap your head around, but fear not! I'm here to help!

If you want to follow along with the code examples in this post at home, I'll be using the following imports from base and random at various points throughout the post:

import Data.Foldable (for_)
import Control.Concurrent (forkIO)
import Control.Concurrent.Chan 
  ( newChan
  , getChanContents
  , writeChan
  )
import Control.Monad 
  ( replicateM
  , replicateM_
  )
import Control.Monad.Reader
  ( lift
  , ask
  , ReaderT
  )
import Control.Monad.ST (runST)
import System.Random.Stateful
import Text.Printf (printf)

The Quick Version

How Do I Generate Random Values Easily Using System.Random.Stateful

Use uniformM to generate a random value that is uniformly distributed in the range of its type.

uniformM :: (Uniform a, StatefulGen g m)
  => g -> m a

Use uniformRM to generate a random value that is uniformly distributed in the given range.

uniformRM :: (UniformRange a, StatefulGen g m)
  => (a, a) -> g -> m a

These functions should work in all kinds of choices of m (the stateful monad).

What the heck is g?

The g type parameter is for the type of the "mutable stateful random number generator", as opposed to System.Random's pure random number generators.

Essentially it is an argument who's data and type (in connection with the type m) inform uniformM and uniformRM how to access and deal with the state nessecary for generating pseudorandom numbers.

Without this, it wouldn't be possible to use uniformRM in the ST s monad or use it with more than one source of state in the same monad.

Unlike its pure cousin you don't have to pass it from one random operation to the next, making it much easier to work with.

What type do I use for g?

Use the following chart, assuming m and g are constrained by StatefulGen g m and pg is constrained by RandomGen pg:

Stateful Monad Choice (m) Stateful generator type (g) How to get a generator
m(staying polymorphic) g Take it as a parameter of a function.
IOor MonadIO m => m(single-threaded) IOGenM pg newIOGenM
IOor MonadIO m => m(shared concurrently) AtomicGenM pg newAtomicGenM or globalStdGen
(MonadState pg m) => m StateGenM pg StateGenM
ST s STGenM pg s newSTGenM
STM TGenM pg newTGenM or newTGenMIO

pg is often instantiated to StdGen.

Examples of use

Polymorphic Pseudo-Randomized Actions

Without ReaderT:

rollDie :: StatefulGen g m => g -> m Int
rollDie = uniformRM (1, 6)

rollDice :: StatefulGen g m => Int -> g -> m [Int]
rollDice n sgen = replicateM n (rollDie sgen)

rollSomeDice :: StatefulGen g m => g -> m [Int]
rollSomeDice sgen = (`rollDice` sgen) =<< rollDie sgen

Having to pass the gen parameter around can be annoying when composing random actions into larger ones. ReaderT g m or any MonadReader g m can help with that.

With ReaderT g m:

rollDie :: StatefulGen g m => ReaderT g m Int
rollDie = lift . uniformRM (1, 6) =<< ask

rollDice :: StatefulGen g m => Int -> ReaderT g m [Int]
rollDice n = replicateM n rollDie

rollSomeDice :: StatefulGen g m => ReaderT g m [Int]
rollSomeDice = rollDice =<< rollDie

Lets stick to the non-ReaderT versions of our randomized operations and for now and put them to use.

The rest of our examples will use our polymorphic actions to show they're truely polymorphic.

Calling In Basic IO

main = do
   sgen <- newIOGenM =<< newStdGen
   rolls <- rollSomeDice sgen
   print rolls

(using an IOGenM StdGen is faster than the AtomicGenM StdGen that globalStdGen gives you)

Calling In Concurrent IO

main = do
  queue <- newChan
  for_ ["Julie", "Simon"] $ \name -> 
    forkIO (diceRoller name queue)
  rolls <- getChanContents queue
  traverse printRoll rolls

mkGen = newIOGenM =<< newStdGen 
 
printRoll = uncurry (printf "%s: %d?\n")

diceRoller name queue = do
  sgen <- mkGen
  replicateM_ 100 $ do
    roll <- rollDie sgen
    writeChan queue (name, roll)

mkGen makes an unshared IOGenM StdGen for a thread from the global shared AtomicGenM StdGen, which prevents threads from competing for posession of the shared generator for long.

Calling in ST

Lets make a System.Random style pure random function out of a procedure that uses local mutable state using ST. (This probably isn't faster than using State to do the same)

rollSomeDicePure :: StdGen -> ([Int], StdGen)
rollSomeDicePure pgen = runST $ do
  sgen <- newSTGenM pgen
  dice <- rollSomeDice sgen
  STGen pgen' <- freezeGen sgen
  pure (dice, pgen')

Full Explanation

Why does System.Random.Stateful exist?

System.Random gives you pure pseudo-random number generators which are immutable. A pseudo-random number generator type will be a member of the class RandomGen

To use the random generator you use functions like:

uniform :: (RandomGen g, Uniform a) => g -> (a, g)

These functions take a pure pseudo-random number generator and return a pseudo-random value and an updated generator, and you have to pass this generator onto any further actions, since if you use the same generator every time, uniform will output the same values every time. That's purity for you!

uniform takes a state and creates a value along with the updated state.

Threading state from from the output of one function call to the input of the next serveral times throughout an application by hand is hard work. Fortunately there are a variety of stateful monads that manage this matter for us.

The only trouble is System.Random leaves the work of turning pure generators and pure randomized value generating functions to the user (except for the IO monad. Pseudo-random value generating actions in IO are provided in System.Random, formerly for convenience, and presently for historical raisins).

Along came MonadRandom: a class (provided by a package of the same name) which provided random value generation methods for any monad that provided an instance.

Intances were provided for any mtl monad tansformer stacke stack built on top of IO or containing (RandomGen g) => RandT g, a transformer that uses the stateful behavior of a newtype wrapped StateT g under the hood to thread around the generator state.

MonadRandom's failings

Lets take a look at the MonadRandom class

class Monad m => MonadRandom m where
  getRandomR  :: Random a => (a, a) -> m a
  getRandom   :: Random a => m a
  getRandomRs :: Random a => (a, a) -> m [a]
  getRandoms  :: Random a => m [a]
  {-# MINIMAL getRandomR, getRandom, getRandomRs, getRandoms #-}

From this we can deduce two things about the methods it provides:

  1. Because there is only one type parameter to this class, each choice of monad m must have only one instance.
  2. There is no argument to vary how or where the generator state is stored, therefore each choice of m must use the "state slot" of it's instance's choosing.

So why are these things an issue?

Well first, when working in IO it's typical to use an IORef to store the generator state.

There are two ways you could use an IORef:

  1. atomically
  2. non-atomically

In a situation where a single IORef is shared between threads, you want to modify the IORef atomically because otherwise if a thread tries to generate a random number before another thread has finished and saved the new state, it will use the same generator state and may generate an identical random value.

However, the atomic access is significantly slower, so in an unshared IORef situation you want to forgo it.

Without an input to vary how the IORef is used and with one instance per choice of m, IO must modify the IORef either atomically or not, and atomically is safer since we are forced to use one IORef for all threads, so that's what the instance should use, but this makes the IO instance slow.

Second, we might want instances for the ST s monad, but an STRef s g reference cannot be broken out of its ST s jail and still be usable with runST

badGlobalSTRef :: STRef s StdGen
badGlobalSTRef = runST (newSTRef $ mkStdGen 0) -- Type error

mostlyUselessGlobalSTRef :: STRef RealWorld StdGen
mostlyUselessGlobalSTRef = unsafePerformIO $ stToIO $ newSTRef $ mkStdGen 1
{-# NOINLINE mostlyUselessGlobalSTRef #-}

main :: IO ()
main = print $
  runST $ readSTRef mostlyUselessGlobalSTRef -- Type error

ST s is constructed with special care so that no two uses of runST can share an STRef, because runST convinces the type checker that a computation using local mutability is a pure computations, which is fine as long as the mutation isn't visible outside the computation's scope.

A shared STRef would mean two different runST performed ST computations would be able to observe each other's stateful effects, so you would get a computation that appears to have no effects according to the type, but secretly has side-effects and violates referential transparency.

Why is this important? Well an instance is a top-level thing. There is no such thing as a locally scoped type class instance, therefore we can't create the MonadRandom (ST s) instance inside an ST s computation, so it cannot get it's hands on a usable STRef, and in fact if it did have it's hands on a usable STRef then this STRef would be shared between ST computations, which would break referential transparency.

So there's no way for the instance to have an STRef unless the methods take an argument that can contain an STRef. If they take an argument then you can simply call the method inside ST s where you can aquire an STRef s g reference and pass it to the call.

Without such an input MonadRandom cannot have an ST s instance.

Loosening the Restrictions

So what's the problem we're actually facing for generalizing the stateful monad our actions are performed in?

Well, to statefully generate a random value we need a state slot and a procedure that can use the state slot to generate a random value and update the state which works in the monad we're currently working in.

It turns out with ST it isn't possible to have evidence that a particular slot of ST state exists at compile time. This must be passed at runtime as an argument.

Our type class means our methods are passed another input implicitly: an instance dictionary, this passes methods their implementation so we can use that to pass in the proof that there is a procedure which can use the passed in state slot evidence to generate a random value.

However, we want a choice of more than one procedure to use the state slot with, since we want to be able to choose between atomic and non-atomic usage of IORef

We could of course pass in an argument which is a combination of stateful reference and and the procedure to use it:

data RandWordGenerator m = forall sr. RandWordGenerator 
  { stateRef :: sr
  , randWordGenProcedure :: sr -> m Word64
  }

generateRandomWord :: RandWordGenerator m -> m Word64
generateRandomWord gen = 
  randWordGenProcedure gen (stateRef gen)

In fact we could just pass in an action to generate a random number that we construct at runime to any procedure that needs it.

newtype RandWordGenerator m =
  RandWordGenerator {generateRandomWord :: m Word64}

mkRandWordGenerator :: sr -> (sr -> m Word64) -> m Word64
mkRandWordGenerator stateRef procedure =
  RandWordGenerator (procedure stateRef)

This is effectively a closure used in the "closures are a poor man's objects" sense. What we're doing here is much like OOP: combining a mutable property and the procedure to use it into a single value to encapsulate the mutable property and hide some details from the code that will use it.

uniformM :: (Uniform a) => RandomWordGenerator m -> m a

uniformM need not be aware of where the state comes from, it merely needs to call generateRandomWord on the random word generator to get an action to generate a random Word64. The mutable slot is encapsulated.

So this combination of state and protocol for using the state is in a sense an object, a state generator object.

However, while we need a choice of procedure, it's fine if we decide this choice at compile time. This would mean deciding the procedure based off of types.

We know our procedure must match the stateful monad we are trying to work in, but we also need more than one procedure per monad, so we need another type as a parameter of our type class which we will use to serve up different implementations of the methods for each instance.

Rather than passing in another argument who's type is used as a parameter to the type class like this:

class MyRandomMonad protocol m where
  type StateRefType protocol m
  randomWord :: Proxy protocol -> StateRefType protocol m -> m Word

We can just use the same input for state reference and protocol choosing type by wrapping a particular state reference in different newtype wrappers to give it a different type, keeping this idea of a state generator object, but making its methods static methods.

class MyRandomMonad generatorObject m where
  randomWord :: generatorObject -> m Word 

In fact when we do things this way, each instance is free to use a generator object that carries as much data as it likes including functions, like dynamic methods, as long as provides the static methods that meet the interface demanded by the type class.

And what do we find in System.Random.Stateful?

class Monad m => StatefulGen g m where
  uniformWord32R :: Word32 -> g -> m GHC.Word.Word32
  uniformWord64R :: Word64 -> g -> m GHC.Word.Word64
  uniformWord8 :: g -> m Word8
  uniformWord16 :: g -> m Word16
  uniformWord32 :: g -> m Word32
  uniformWord64 :: g -> m Word64
  uniformShortByteString :: Int -> g -> m ShortByteString
  default uniformShortByteString :: MonadIO m =>
    Int -> g -> m ShortByteString
  {-# MINIMAL (uniformWord32 | uniformWord64) #-}

Ah, so thig g is our object-like parameter type which may carry some data including a mutable reference, and our choice of g and m picks the implementation of StatefulGen's methods which are then able to use any data g carries.

Unlike MonadRandom which makes the m the central focus of the class, StatefulGen names itself this conceptual meaning of the g parameter.

The methods of StatefulGen only generate words and bytestrings but from these you can write functions to generate other kinds of values.

The most common thing you'll want to do is generate uniformly distributed random values of various types, so there are type classes for that:

class Uniform a where
  uniformM :: StatefulGen g m => g -> m a
  default uniformM :: 
    (StatefulGen g m, Generic a, GUniform (Rep a)) =>
      g -> m a

class UniformRange a where
  uniformRM :: StatefulGen g m => (a, a) -> g -> m a
  {-# MINIMAL uniformRM #-}

So StatefulGen methods are mostly used to implement instances of Uniform and UniformRange for a type.

System.Random.Stateful provides many instances of Uniform out of the box so you don't have to worry about the methods of StatefulGen most of the time.

Assuming the type you want to generate random values for already has a Uniform instance, mostly you will just use uniformM and uniformRM which are the stateful generator counterparts to uniform and uniformR (which are the modern replacements for random and randomR that guarantee a uniform distribution).

Freezing a Stateful Generator

Suppose we want to make a randomized game where we can undo turns. For instance, maybe we are fighting a grue and we can take a turn to light a match or attempt to stab at the grue in the dark.

Attempting to light a match doesn't always work in one turn, and we have a good chance of missing when we take a stab in the dark, but every turn we have a chance of getting eaten by the grue.

If we aren't careful, a player can always just try to stab the grue and undo the turn if they miss, rerolling until they hit. This practive of restoring a saved state to avoid bad rolls is known as "save scumming".

Suppose we want to prevent save scumming. We might want it so that if a player tries an action, recieves a randomized outcome, undoes and tries the same action, they recieve the same outcome such that any fixed series of choices beginning at the game start is always "fated" to have the same outcome once the state generator has been initialized, no matter how much you undo.

To do this you need to be able to save the game state including the current generator state, and restore the stateful generator from a previous state.

If you merely try to make a copy of the stateful generator and avoid using the copy while continuing to use the original, you'll find that when you try to restore by switching back to the copy, it has the same state the original generator had.

This is because of two reason: first, most likely your attempt to "copy" the state generator just created another variable referencing the same stateful generator, and even if you did make an in-memory copy of the value, the value of the stateful generator doesn't actually store the state. It at most contains a reference to a mutable location, so making a copy most likely just makes a copy of the reference to the same mutable location.

For IORef and STRef you could make an action that makes a new generator with a new reference containing a copy of the state stored in the old generator's mutable reference, but this wouldn't work in StateT where there is only one state slot shared by all StateGenM generators.

The more sensible thing is to just have an operation to make a frozen immutable copy of a stateful generator that won't change if the original generator continues to be used.

Enter FrozenGen:

class StatefulGen (MutableGen f m) m => FrozenGen f m where
  type MutableGen :: * -> (* -> *) -> *
  type family MutableGen f m = g | g -> f
  freezeGen :: MutableGen f m -> m f
  thawGen :: f -> m (MutableGen f m)
  {-# MINIMAL freezeGen, thawGen #-}

You can view instances of this class as:

  1. A promise that there is a frozen generator type (f) and a monad it can be frozen (and thawed) in (m), from some particular non-frozen stateful generator that can be referred to with the type synonym MutableGen f m, where you must be able to infer f if you know what type MutableGen f m stands for.

  2. Proof of the above promise in the form of definitions of the methods to do such things.

The part where you must be able to infer f when you know MutableGen f m means that every non-frozen stateful gen type must have only one frozen generator type counterpart.

If you take a look at the instances you will see that available choices for f include AtomicGen g, IOGen g, StateGen g and STGen g. Each of these is a newtype wrapper around the pure generator value of the type stored in the MutableGen f m version's mutable slot.

So just to clarify, a mutable reference in Haskell points to immutable values. The mutating part is changing what the reference is pointing to, not changing the values themselves. This is of course not unusual for a language. In C if you do

int x = 1;
x += 2;

This doesn't fundamentally change every 1 in your program to 3, it just changes which value x contains.

This is why inside the mutable slot of a stateful generator there is a pure generator.

Now you might wonder why then freezeGen applied to IOGenM g returns the g wrapped in IOGen rather than just g. Why does each mutable generator need to freeze to a special type rather than just the pure generator it stores?

Well remember: each stateful generator doesn't just convey information in its data representation. The type itself conveys information that directs the compiler in instance selection, so IOGenM g and AtomicGen g may both contain mutable references to a g, but if you freeze to g alone you can't tell whether the g was frozen from an IOGenM g or an AtomicGen g, which would make it impossible to thaw back to the same mutable generator type.

So the newtype wrappers act as tags to indicate what type of stateful generator the wrapped pure generator was frozen out of.

Converting From Pure To Stateful Randomization

As we've seen, the stock generators are often treated as mutably containing some type of pure generator. IOGenM g actually contains a mutable reference to a g, StateGenM g does not contain a g but it's instances aquire the g held a StateT g containing monad.

So one might want to convert from a pure random value generating function to a stateful one.

Enter RandomGenM:

class (RandomGen r, StatefulGen g m) =>
  RandomGenM g r m | g -> r where
    applyRandomGenM :: (r -> (a, r)) -> g -> m a
  {-# MINIMAL applyRandomGenM #-}

The RandomGenM class relates a type with a RandomGen instance (r) to its corresponding stateful gen (g). The functional dependency ensures each choice of g must have one and only one related r.

The method obviously turns pure random value generating functions into stateful generator using actions.

Both FrozenGen and RandomGenM are separate classes from StatefulGen so that not every stateful generator has to implement them.

Maybe you want to write a stateful generator that works by using a hardware random number generator for every operation, who's state cannot be frozen and which can't supply a pure generator to psuedo-random number generator functions. You can do that and any random algorithm that will work for any StatefulGen instance will work with that generator, but algorithms that require freezing obviously won't since the FrozenGen state cannot be satisfied.

Hopefully you now know enough figure to out the rest of the System.Random.Stateful documentation on your own.