Unit Testing is a great way to try to verify consistent functionality over the life of our code. Typically we design our tests to cover ranges and edge cases of our code making sure that we can handle all inputs. This is made easy when we write in Functional Languages as there (should be) no side effects. But when you want to deal with IO and side affect code in Haskell, this becomes much more difficult.
This problem has been fixed many times, but often with very complex solutions. Let's see if we can make it really simple (even if the post is long).
If you want to play along the code is availabe from git or [zip file][7]
git clone https://commentedcode.org/git/blog/mockio.git
While learning how to use [fltkhs][1], and creating a GUI [Diceware][2] password generator, I realized that I was going to be doing a lot of work in the IO
Monad. For the GUI parts I didn't really care to do a lot of unit testing so I didn't think there would be much of an issue.
When we think of IO
we often think of interacting with the User.
helloWorld :: IO () helloWorld = do putStr "What is your name? " name <- getLine putStrLn $ "Hello " ++ name
The IO
Monad is used for other interactions such as random number generation. Here is a simple function that simulates rolling an "n-sided" die.
rollDice :: Int -> IO Int rollDice sides = getStdRandom $ randomR (1,sides)
Using the repl we can see that our function returns numbers, but since its random we can't really see if the range of outputs are valid or not.
>>> rollDice 6 5 >>> rollDice 6 3 >>>
What makes this even worse is that because the value returned is random, doing any sort of edge case testing on code that uses this function is nearly impossible.
Per [Wikipedia][2]
In object-oriented programming, mock objects are simulated objects that mimic
the behavior of real objects in controlled ways. A programmer typically
creates a mock object to test the behavior of some other object
Even though we are not working with a OO language, we can still take the concept of a Mock Object and apply it here. What better use for Monads than to create simulated scenarios to mock possible real world use cases.
The feature of Monads we will be using deals with the fact that they allow us to temporarily modify the normal rules of haskell. This, of course, is done in a controlled way as to keep things still within the realm of typical Haskell and FP.
Being a pure functional language, Haskell functions are [referentially transparent][3]. This means that no matter the state of the application or the system it runs on, a function will always return the same result given an input. sin()
will always return 0
when given the value pi
. toUpper
always returns "HELLO"
when given "hello"
.
Think about what rules change in haskell when you are in the IO
Monad. When you call getLine
the string returned is dependent on the user at the keyboard and two individuals may type two different values. This means that getLine
is not referentially transparent. Within the context of the IO
monad, its OK that this function doesn't follow Haskell's rules.
Haskell is also a (mostly) immutable language. New values are stored under new names, while old ones are cleaned up. Counters in loops don't exist, but instead are passed in as a counting argument into a recursive function. Updating values just isn't done.
But when you introduce the State
Monad the rule of immutability is no more. Again, its a controlled manipulation of the rules, but you are able to change the application's state through a mutable object.
So what rules do we want to bend for our testing purposes?
To repeat our problem, when running a unit test we can't rely on non-referentially transparent functions like getLine
and randomR
to give us consistent values. Because of this, it would be possible for a test to fail on one run, and be successful on another. This does not make for good testing.
What if we could write our code that uses the IO
monad when we were running normally, but then run a special monad that mock's the IO
monad when we do our testing? Then we could produce consistent results with our unit tests without having to redesign our code, or do modifications between runtime and test time.
This is where [Type Classes][4] come in. Type Classes are a way for Haskell to provide a polymorphic interface to types. You can define a set of functions and group them into a type class. Then you can declare instances of the type class with data types that exist, providing the implementation of its group of functions with relation to the instance that data type.
The Eq
type class is used for testing equality. Members of the type class must provide (==)
and (/=)
implementations so that you can compare two value to be equal or not.
-- Person: Name Age data Person = Person String Int instance Eq Person where -- Both Persons are equal if they have the same Name and Age (Person n1 a1) == (Person n2 a2) = n1 == n2 && a1 == a2
The Ord
type class is used for ordering items, with the following definition:
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
Here we see that all members of the Ord
type class must provide implementation to a hand full of different functions used for ordering. On the first line we also see (Eq a)
which tells us that all types that are an instance of Ord
must also be an instance of Eq
. This makes sense since you'd be able to use equality during your ordering process.
Even monads are represented as type classes.
class Applicative m => Monad (m :: * -> *) where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a fail :: String -> m a
All Monads are Applicatives, with bind, return, and fail functions.
Let's create our own type class. One that requires all the IO functions we will be using in our code that might affect our unit testing.
For our first operation we'll write a string to an output. In the Prelude
library we have the following function:
putStr :: String -> IO ()
A String
is passed to the function, the value is written to stdout and then returns unit ()
...all occurring within the context of the IO
monad. What we need to do is define our type class that works both within the IO
monad as well as other monads. Since Monad
is a type class, we can write our type class to only allow derived types to be part of the Monad
class (just like Ord
and Eq
).
class Monad m => MockIO m where mPutStr :: String -> m ()
Our function mPutStr
takes a String
as an argument and then does "something" within the context of the m
monad and returns unit ()
. In the IO
monad we want that "something" to be writing to stdout. And since the signature of our function matches that of putStr
we can easily define that for our IO
instance of MockIO
:
instance MockIO IO where mPutStr = Prelude.putStr
We can do the same for putStrLn
and getLine
. For our random number generator we'll define it to make our dice rolling simpler.
-- src/MockIO.hs module MockIO where class Monad m => MockIO m where mPutStr :: String -> m () mPutStrLn :: String -> m () mGetLine :: m String mGetRandomInt :: Int -> Int -> m Int mPutStrLn s = mPutStr $ s ++ "\n"
Here is the runtime implementation for IO
.
-- src/MockIO/IO.hs module MockIO.IO where import System.Random import MockIO -- |Instance of MockIO for runtime execution with IO instance MockIO IO where mPutStr = Prelude.putStr mPutStrLn = Prelude.putStrLn mGetLine = Prelude.getLine mGetRandomInt min max = getStdRandom (randomR (min, max))
Let's go back to our dice rolling code and rewrite it using our new MockIO
type class.
rollDice :: MockIO m => Int -> m Int rollDice sides = mGetRandomInt 1 sides
Pretty simple. We define our type m
as an instance of MockIO
and then use functions from within that type class. If we load this code up in the repl we get:
>>> import MockIO >>> Import MockIO.IO >>> Import Dice >>> rollDice 6 4 >>> rollDice 6 6 >>> rollDice 6 2 >>>
Since the repl is always running within the IO
monad, we use the IO
instance functions.
So where does this get us? We now have the ability to call IO
functions when we are working within IO
. But in unit testing we want to remove the random results of IO
with something fixed.
The State
monad allows us to create a mutable state variable that exists during the context of the monad. We can use this monad to store expected values and return them as if they were pulled from IO. A simple explanation of State
can be found at [LYaH][5].
The first step is to create the data type that will store our state. We want to provide fixed values for stdin and for random numbers, and it would be nice to store off things written to stdout.
data MockState = MockState { outputs :: [String] -- Strings the mock will output, like getLine , inputs :: [String] -- Strings the mock will input, like putStr , outputInts :: [Int] -- "Random" ints we will return in mGetRandomInt } deriving (Show, Eq)
Pretty simple, just a set of arrays contained inside a data type. We will derive Show
and Eq
type classes as to make debugging easier.
newtype State s a = State { runState :: s -> (a,s) }
where `s` is the state information and `a` is the return type. The `runState` function is used to execute a function within the context of the `State` monad. Our use case with our new state object will be:
State MockState a = State { runState :: MockState -> (a,MockState) }
Rather than always typing `State MockState` we can define our own type:
type SimpleMockedIO = State MockState
runMockIO :: SimpleMockedIO a -> MockState -> (a, MockState)
runMockIO = runState
For our unit test setup we will use a `MockState` to setup our environment and then execute the code using these new functions and data types. For example, we can use our dice rolling function and test that it returns the correct value. We call `rollDice` within the `SimpleMockedIO` context giving the following function definition and we see the change:
:t rollDice
rollDice :: MockIO m => Int -> m Int
:t runMockIO (rollDice 6)
runMockIO (rollDice 6) :: MockState -> (Int, MockState)
Given a `MockState` this curried function would return an `Int` and the mutated state.
let env = MockState [] [] [1] -- Ouputs, Inputs and Random Numbers
let (result, _) = runMockIO (rollDice 6) env
result
1
We defined the value returned from our "random number generator" and sure enough that is the value. Lets test it even more.
let env = MockState [] [] [1,2,3,4,5,6]
:{
let test :: MockIO m => m [Int]
test = do
r1 <- rollDice 6
r2 <- rollDice 6
r3 <- rollDice 6
r4 <- rollDice 6
r5 <- rollDice 6
r6 <- rollDice 6
return [r1, r2, r3, r4, r5, r6]
:}
let (res,_) = runMockIO test env
res
[1,2,3,4,5,6]
Six rolls and six exactly as expected results. So how is this done? ### Pretend to be IO Just like we did with the `IO` monad making it an instance of `MockIO`, we need to do the same with our new state monad `SimpleMockedIO`. For each of the functions we need to retrieve the current state, do whatever IO is necessary and then update the state for future use. Let's take a look at how the random numbers are handled.
instance MockIO SimpleMockedIO where
mGetRandomInt min max = do
st <- get
case outputInts st of
[] -> error "MOCK ERROR: Empty random number generator"
(i:ix) -> do
if i < min || i > max
then error "MOCK ERROR: Bad Values in Random Number Generator"
else do
let newSt = st { outputInts = ix }
put newSt
return i
We set the current state to `st` and then check to see if we have any numbers left in our mock environment. We check to make sure the next value is within our min and max (as we assume the way `IO` handles this would always work). Lastly we update the state by removing the number from the list, saving the new state off and returning our "random" number. Writes to stdout are handled by concatenating to a list and reads are done in a similar way as the random numbers, just with `String` instead of `Int`.
-- src/MockIO/Simple.hs
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE InstanceSigs #-}
module MockIO.Simple where
import Control.Monad.State
import Data.Functor.Identity
import MockIO
-- | MockState is a data structure used for simple mocking of IO
-- This data type contains intput, and output strings to simulate stdin and stdout
-- as well as a list of integers for a random number generator.
data MockState = MockState
{ outputs :: [String] -- getLine
, inputs :: [String] -- putStr(Ln)
, outputInts :: [Int] -- mGetRandomInt
}
deriving (Show, Eq)
-- |SimpleMockedIO is the data type that simulates the runtime environment
-- See runMockIO for details on simulating IO
type SimpleMockedIO = State MockState
-- |runMockIO simulates IO returning the state after execution
runMockIO :: SimpleMockedIO a -> MockState -> (a, MockState)
runMockIO = runState
-- |Instance example of MockIO for simulation
-- Defines access to inputs, outputs and random numbers.
instance MockIO SimpleMockedIO where
mPutStr str = do
st <- get
let newSt = st { inputs = str:inputs st }
put newSt
return ()
mGetLine = do
st <- get
case outputs st of
[] -> error "MOCK ERROR: Empty stdin"
(o:ox) -> do
let newSt = st { outputs = ox }
put newSt
return o
mGetRandomInt min max = do
st <- get
case outputInts st of
[] -> error "MOCK ERROR: Empty random number generator"
(i:ix) -> do
if i < min || i > max
then error "MOCK ERROR: Bad Values in Random Number Generator"
else do
let newSt = st { outputInts = ix }
put newSt
return i
## Conclusion...our Unit Test Works!!!
-- test/DiceSpec.hs
module DiceSpec where
import Test.Hspec (Spec, describe, it, shouldNotBe, shouldThrow, errorCall)
import Dice (rollDice)
import MockIO.Simple
spec :: Spec
spec = do
describe "Rolling Dice" $ do
it "Rolls all numbers between 1 and 6" $ do
let env = MockState [] [] [1,2,3,4,5,6]
let test :: MockIO m => m [Int]
test = do
r1 <- rollDice 6
r2 <- rollDice 6
r3 <- rollDice 6
r4 <- rollDice 6
r5 <- rollDice 6
r6 <- rollDice 6
return [r1, r2, r3, r4, r5, r6]
let (res,_) = runMockIO test env
res `shouldBe` [1,2,3,4,5,6]
While this isn't the most glamorous way of solving this problem, it does allow us to swap out `IO` for `State` which is what we needed to make our unit tests work. This solution can be extended to mock network traffic, interactions with a database or pretty much anything you want. It doesn't require a lot of knowledge in advanced topics, having almost everything in here being covered in [Learn You a Haskell][6]. Lastly, if you were worried that now all of your IO functions would be using this `MockIO` type class and not be portable, like if you were wanting to write a public library, don't worry. We can easily expose functions that have the correct `IO` monad type you want.
-- src/Dice.hs
module Dice where
import MockIO
import MockIO.IO
rollDice :: MockIO m => Int -> m Int
rollDice sides = mGetRandomInt 1 sides
rollDiceIO :: Int -> IO Int
rollDiceIO = rollDice
Since `IO` is an instance of `MockIO`, our definition of `rollDiceIO` just refines which `MockIO` instances will be using. Internally you'll use the `MockIO` version of code, along with your unit tests, but only publicly expose the `IO` only version.
import Dice
:t rollDice
rollDice :: MockIO m => Int -> m Int
:t rollDiceIO
rollDiceIO :: Int -> IO Int
text/gemini
This content has been proxied by September (ba2dc).