[Haskell-cafe] A Random Question

Dominic Steinitz dominic.steinitz at blueyonder.co.uk
Sat Dec 15 09:22:12 EST 2007


Paul Johnson wrote:
> Dominic Steinitz wrote:

> Unfortunately for your purpose you would need:
> 
> *generate* :: (RandomGen g) => Int
> <http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Int.html#t%3AInt>
> -> g -> Gen
> <http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickCheck.html#t%3AGen>
> a -> a

Thanks - rather what I thought.

This seems to do the trick using a state monad but it doesn't look pretty.

import Test.QuickCheck
import Control.Monad.State

data Baz = Baz String Int
   deriving (Eq, Show)

g :: MonadState Int m => m (Gen Int)
g =
   do x <- get
      put (x + 1)
      return (return x)

f :: MonadState Int m => Int -> m (Gen [Baz])
f 0 = return (return [])
f n =
   do x <- g
      xs <- f (n - 1)
      let z = do u <- x
                 us <- xs
                 v <- arbitrary
                 return ((Baz ("t" ++ (show u)) v):us)
      return z


*Main> let (q,p) = runState (f 10) 1 in sample q
[Baz "t1" (-1),Baz "t2" 0,Baz "t3" 0,Baz "t4" (-1),Baz "t5" 1,Baz "t6"
1,Baz "t7" 1,Baz "t8" 1,Baz "t9" 1,Baz "t10" 1]
[Baz "t1" 0,Baz "t2" 2,Baz "t3" (-2),Baz "t4" (-2),Baz "t5" (-1),Baz
"t6" 0,Baz "t7" 1,Baz "t8" 2,Baz "t9" (-2),Baz "t10" (-2)]

This gives me what I wanted: distinct (and in this case predictable)
names and random values.

> 
> Take a look at SmallCheck.  It might be more suited to your requirement
> anyway.
> 

I will do so now.

Thanks, Dominic.



More information about the Haskell-Cafe mailing list