HMock with MonadRandom
One effect that can complicate tests is randomness. The random library provides a pure API for pseudo-random number generation, and a constant seed can be used to get repeatable results that are suitable for testing. A test can be written by first specifying the constant seed and then adjusting the test to use the values that are generated given that seed, which is somewhat inelegant. Would it be possible to instead use HMock with MonadRandom to mock random value generation at a high level?
The MonadRandom type class provides the following methods:
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]
Unfortunately, it cannot be used with HMock directly because the methods have polymorphic return types that are not Typeable. The HMock documentation indicates that a Typeable constraint must be added to methods in order to match exact calls. Attempting to use makeMockable results in the following error:
/path/to/Experiment.hs:24:1: error:
Cannot derive Mockable because Control.Monad.Random.Class.MonadRandom has no mockable methods.
|
24 | HMock.makeMockable [t|MonadRandom|]
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
As an experiment, I tried defining a “wrapper” class, a tactic
similar to the one I used in the Mocking FileStatus blog
entry. The class is the same as MonadRandom
except that it adds a Typeable
constraint to all of the methods. The DefaultSignatures
extension is used to delegate the implementation to the MonadRandom
instance, with INLINE
pragmas to ensure that no overhead is
introduced by the wrapper.
class Monad m => MonadTypeableRandom m where
getRandomR :: (Rand.Random a, Typeable a) => (a, a) -> m a
default getRandomR :: (Rand.MonadRandom m, Rand.Random a, Typeable a)
=> (a, a) -> m a
= Rand.getRandomR
getRandomR {-# INLINE getRandomR #-}
getRandom :: (Rand.Random a, Typeable a) => m a
default getRandom :: (Rand.MonadRandom m, Rand.Random a, Typeable a)
=> m a
= Rand.getRandom
getRandom {-# INLINE getRandom #-}
getRandomRs :: (Rand.Random a, Typeable a) => (a, a) -> m [a]
default getRandomRs :: (Rand.MonadRandom m, Rand.Random a, Typeable a)
=> (a, a) -> m [a]
= Rand.getRandomRs
getRandomRs {-# INLINE getRandomRs #-}
getRandoms :: (Rand.Random a, Typeable a) => m [a]
default getRandoms :: (Rand.MonadRandom m, Rand.Random a, Typeable a)
=> m [a]
= Rand.getRandoms
getRandoms {-# INLINE getRandoms #-}
As mentioned in the HMock with DefaultSignatures blog entry, makeMockable is incompatible with DefaultSignatures in the current release. Chris Smith approved my fix, so I submitted a pull request this morning. With the fix applied, makeMockable works with the above class.
HMock.makeMockable [t|MonadTypeableRandom|]
I used to the following trivial example function to test:
example :: MonadTypeableRandom m => m Bool
= (== 0) <$> getRandomR (0, 1 :: Int) example
The test case matches the exact call and returns a constant return value:
"experiment" . HMock.runMockT $ do
testCase $ GetRandomR_ anything |=>
HMock.expect GetRandomR (0, 1 :: Int)) -> pure 0
\(. assertBool "True" =<< example liftIO
This kind of wrapper class could be used in simple cases where MonadRandom is only used directly, but it does not help in the more common cases where MonadRandom is (also) used via libraries. In some cases, it might be worth creating type classes that represent the randomness used in the application at a high level. The implementations of the methods could use MonadRandom internally, while MonadRandom is kept out of other application functions. Otherwise, one can simply add a StdGen value to the state of the application monad (or use RandT) and test using a constant seed as usual.
The above code is available on GitHub.