Enlico
Enlico

Reputation: 28470

How can I unit-test computations that happen in a monadic transformer stack with an IO base layer?

Below is very simplified version of a program I wrote¹, where I have some read-only state (e.g. screen size, etc) made available via ReaderT, and some mutable state (the state of the game) that I interact with via the StateT layer. Unfortunately, I need MonadIO, mostly for printing to screen and to generate random numbers.

module Main where

import MTLPrelude
import System.Random

main :: IO ()
main = do
  let s0 = "inital state"
  let env = "read-only env"
  sEnd <- computation `execStateT` s0 `runReaderT` env
  print sEnd

computation :: (MonadIO m,
                MonadState String m,
                MonadReader String m)
            => m ()
computation = do
  e <- ask
  s <- get
  i <- liftIO $ randomRIO (0 :: Int, 10)
  put $ s ++ e ++ show i

(In the real case, computation layers not only a MonadState and MonadReader, but also MonadWriter and MaybeT; see link at the bottom of the question for full code.)

I have managed to break computation in ((some >>= distinct >>= logical) <* actions >>= chained >> together).

Luckily some of them don't need MonadIO, so they can be easily tested; others only need MonadIO, e.g. one bit just sleeps for a fraction of a second; but those are the less complex one, so there's not even much to test.

The more complex actions, instead, do rely on MonadIO plus some other layer (one or more of those I mentioned), which I have exemplified in the snippet above by using randomRIO, which makes them not testable (not as easily as I would do with pure functions via QuickCheck, at least).

How can I rewrite the above code, or rething the whole approach, so that I can make functions more testable?

Further thoughts:

  1. One approach I initially thought of is that I could use reader layer to pass relevant IO actions, e.g. putStr and randomRIO, down the stack, but this would probably not help me achieve anything, because actually performing those actions would still require the whole stack to be powered with IO (explicitly or via MonadIO constraint). For instance, I could change the above code to this:

    -- same imports
    main :: IO ()
    main = do
      let s0 = "inital state"
      let env = "read-only env"
      sEnd <- computation `execStateT` s0 `runReaderT` (env, randomRIO)
      print sEnd
    
    computation :: (MonadIO m,
                    MonadState String m,
                    MonadReader (String, (Int,Int) -> IO Int) m)
                => m ()
    computation = do
      (e, io) <- ask
      s <- get
      i <- liftIO $ io (0 :: Int, 10)
      put $ s ++ e ++ show i
    

    but I still have liftIO and MonadIO around, so testing would still require that I write some IO action that mocks the real one.

  2. Then I thought that maybe the ideal would be to swap the IO used by the real program to print characters to change the state of the screen, with State String, where the String would represent the screen.


I am aware of this thread, but I don't consider it a duplicate because I'm asking about a more specific scenario than in that question, where there's no mention of transformers stacks.


(¹) It's the game Snake, which I'm doing as an excuse to approach game development in Haskell. Here is the repo, in case you want to give a look, even just to better contextualize my question above.

Upvotes: 1

Views: 63

Answers (1)

ShapeOfMatter
ShapeOfMatter

Reputation: 1021

You absolutely can test IO programs with QuickCheck. The key function is ioProperty. Whether or not that suffices depends on what you're trying to do.

For the given example of randomness, ioProperty is probably all you need. Figure out some data Args = ... with instances for Arbitrary and Show, and define your test as a function:

myTest Args{...} = ioProperty do ...
                               return $ validate results ...

If the thing you want to mock is interaction with a user, or some similar "real world" IO that you want to fake for testing, then the situation is more difficult. The solution I've used in the past is to introduce a "shim" in the monad stack that affords the relevant actions (e.g. reading from stdIn, writing to stdOut). You'd have two handlers for this shim, one of which passes the actions through to IO, and the other of which mocks the behavior using State (or whatever).

I can point to an example of actually doing this here, but I should warn you that there's a lot of other stuff going on in that repo; maybe someone else knows a cleaner example. All of the case studies in there use CLI IO as their "local" monad. (I'm pretty sure CLI itself doesn't really need to be parameterized; I think the interior is always IO.) If you want to actually run the example programs, you use runCLIIO, but in Tests.hs they use runCLIStateful, which consumes a tape of inputs and yields a tape of outputs.

Upvotes: 1

Related Questions