[Haskell-cafe] Using MonadRandom with QuickCheck

Li-yao Xia li-yao.xia at ens.fr
Sun Aug 21 20:37:28 UTC 2016


Hi Magnus,

Import Test.QuickCheck.Gen to get the internals of Gen, which AFAIK is 
currently the only way to get to the underlying random generator (QCGen).

getRandom = MkGen $ \g _ -> fst (random g)
-- repeat with randomRs, randoms.

I don't know why Gen is not an instance of MonadRandom either. It seems 
reasonable to add one, though it might go against some design principle 
of QuickCheck by ignoring the size parameter.

Regards,
Li-yao

On 08/21/2016 09:38 PM, Magnus Grindal Bakken wrote:
> Is there some easy way to use the Gen type from QuickCheck with the
> MonadRandom class?
>
> Links to the packages in question:
> https://hackage.haskell.org/package/MonadRandom
> https://hackage.haskell.org/package/QuickCheck
>
> Some background in case there's an easier way to solve the problem:
> I'm toying around with an API for a simple turn-based board game. The
> main type in my API is called GameState, and I'm trying to define an
> Arbitrary instance for it so I can set up invariants with QuickCheck.
> The Arbitrary instance should produce game states that are the result
> of playing a random number of random moves.
>
> At certain points in the gameplay the game itself needs to invoke some
> randomness. I've designed the public game API to have basically just
> two functions:
>
> playAction :: ActionData -> GameState -> GameState
> evaluateGameState :: MonadRandom m => GameState -> m GameState
>
> The usage is supposed to be that the client first calls playAction
> with an ActionData value that depends on the current move, and
> afterwards calls evaluateGameState to evaluate whatever random events
> need to happen at that point (e.g. reshuffling a deck of cards). That
> way my main "action" logic doesn't need to concern itself with any
> form of randomness.
>
> I'm using MonadRandom from Control.Monad.Random because it seems like
> a much nicer way to generate random numbers than using RandomGen
> directly. However I can't figure out how to make it play nice with
> QuickCheck. I can easily set up my Arbitrary instance to call
> playAction an arbitrary number of times, but I can't call
> evaluateGameState since it lives in the other monad. It would work if
> Gen were an instance of MonadRandom, but I can't quite work out how to
> write that instance since most functions on Gen only work if the
> output type is an instance of Arbitrary, while MonadRandom needs to
> work with any types that are part of the Random class. This part
> works:
>
> instance MonadRandom Gen where
>     getRandomR = choose
>
> But I don't know how to define the other functions on MonadRandom for Gen.
>
> I think I might also be able to use the PropertyM monad transformer:
> https://hackage.haskell.org/package/QuickCheck-2.9.1/docs/Test-QuickCheck-Monadic.html,
> but monad transformers always confuse me so I haven't been able to
> figure out how to do that yet either.
>
> I've thought about rewriting the API to use the Gen type instead of
> MonadRandom, but it feels kind of iffy to have the API depend on a
> testing library.
>
> Has anyone tried to use these libraries together before?
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>


More information about the Haskell-Cafe mailing list