Haskell logo CIS 552: Advanced Programming

Fall 2019

  • Home
  • Schedule
  • Homework
  • Resources
  • Style guide
  • Syllabus
Note: this is the stubbed version of module RandomGen. You should download the lhs version of this module and replace all parts marked undefined. Eventually, the complete version will be made available.

In class exercise: Random Generation

> {-# LANGUAGE ScopedTypeVariables #-}
> module RandomGen where
> import System.Random (StdGen, next, randomIO)
> import qualified System.Random as Random (mkStdGen)
> import State
> import Control.Monad

Random Generation

Recall that QuickCheck needs to randomly generate values of any type. It turns out that we can use the state monad to define something like the Gen monad used in the QuickCheck libary.

First, a brief discussion of pseudo-random number generators. Pseudo-random number generators aren't really random, they just look like it. They are more like functions that are so complicated that they might as well be random. The nice property about them is that they are repeatable, if you give them the same seed they will produce the same sequence of "random" numbers.

Haskell has a library for Pseudo-Random numbers called System.Random. It features the following elements:

type StdGen  -- A type for a "standard" random number generator.

-- | Construct a generator from a given seed. Distinct arguments
-- are likely to produce distinct generators.
mkStdGen :: Int -> StdGen

-- | Returns an Int that is uniformly distributed in a range of at least 30 bits.
next     :: StdGen -> (Int, StdGen)

Side note: the default constructor mkStdGen is a bit weak so we wrap it to perturb the seed a little first:

> mkStdGen :: Int -> StdGen
> mkStdGen = Random.mkStdGen . (* 3 ^ 20)

For example, we can generate a random integer by constructing a random number generator, calling next and then projecting the result.

> testRandom :: Int -> Int
> testRandom i = fst (next (mkStdGen i))

If we'd like to constrain that integer to a specific range (0, n) we can use nextBounded. See if you can define that operation. (NOTE: this generator must always return a result. However, if the range is empty, then the result could be anything.)

> nextBounded :: Int -> StdGen -> (Int, StdGen)
> nextBounded bound s = undefined
> -- test `nextBounded` with 20 randomly generated numbers, using the bound n
> testBounded :: Int -> Bool
> testBounded n = all (\x -> x >= 0 && x < n) (g n <$> [0 .. 20]) where
>     g x = fst . nextBounded x . mkStdGen

QuickCheck is defined by a class of types that can construct random values. Let's do it first the hard way... i.e. by explicitly passing around the state of the random number generator

> -- | Extract random values of any type
> class Arb1 a where
>    arb1 :: StdGen -> (a, StdGen)
> instance Arb1 Int where
>    arb1 = next
> instance Arb1 Bool where
>   arb1 = undefined
> testArb1 :: Arb1 a => Int -> a
> testArb1 = fst . arb1 . mkStdGen

What about for pairs?

> instance (Arb1 a, Arb1 b) => Arb1 (a, b) where
>   arb1 = undefined

NOTE: make sure that you don't always generate the same number for a pair of Ints. If you get this behavior, you have a bug:

ghci> testArb1 20 :: (Int, Int)
(77051893,77051893)
ghci> testArb1 2021 :: (Int, Int)
(1504617061,1504617061)

And for lists?

> instance Arb1 a => Arb1 [a] where
>   arb1 s = undefined

Although we don't have QCs combinators available, you should be able to control the frequency of when cons and nil is generated so that you get reasonable lists.

ghci> testArb1 2 :: [Int]
[1000038160,1595063297]
ghci> testArb1 3 :: [Int]
[]
ghci> testArb1 4 :: [Int]
[2054794989,327347192,267611348,863499775]

Ouch, there's a lot of state passing going on here.

State Monad to the Rescue

Previously, we have developed a reusable library for the State monad. Let's use it to define a generator monad for QuickCheck.

Our reusable library defines an abstract type for the state monad, and the following operations for working with these sorts of computations.

type State s a = ...

instance Monad (State s) where ...

get      :: State s s
put      :: s -> State s ()

runState :: State s a -> s -> (a,s)

Now let's define a type for generators, using the state monad.

> type Gen a = State StdGen a

With this type, we can create a type class similar to the one in the QuickCheck library.

> class Arb a where
>   arb :: Gen a

For example, we can use the operations on the state monad to access and update the random number generator stored in the State StdGen a type.

> instance Arb Int where
>   arb = do
>     s <- get
>     let (y, s') = next s
>     put s'
>     return y

What if we want a bounded generator?

> bounded :: Int -> Gen Int
> bounded b = undefined

Now define a sample function, which generates and prints 10 random values.

> sample :: Show a => Gen a -> IO ()
> sample gen = do
>   seed <- (randomIO :: IO Int) -- get a seed from the global random number generator
>                                -- hidden in the IO monad
>   undefined

For example, you should be able to sample using the bounded combinator.

ghci> sample (bounded 10)
5
9
0
5
4
6
0
0
7
6

What about random generation for other types? How does the state monad help that definition? How does it compare to the version above?

> instance (Arb a, Arb b) => Arb (a,b) where
>  arb = undefined

Can we define some standard QuickCheck combinators to help us? What about elements, useful for the Bool instance ?

> elements :: [a] -> Gen a
> elements = undefined
> instance Arb Bool where
>   arb = elements [False, True]

or frequency, which we can use for the [a] instance ?

> frequency :: [(Int, Gen a)] -> Gen a
> frequency = undefined
> instance (Arb a) => Arb [a] where
>   arb = frequency [(1, return []), (3, (:) <$> arb <*> arb)]

Of course, QuickCheck does a lot more than this, as you can tell from sampling. In particular, QC keeps track of more information, such as size controls, during repeated uses of arbitrary. Furthermore, QC also stores all of its state inside the IO monad instead of using the State monad. However, this exercise should have given you more practice with the state monad, as well as a better understanding of what is going on under the hood with QuickCheck.

Design adapted from Minimalistic Design | Powered by Pandoc and Hakyll