Modules and Tests
This page describes one way of writing and running tests in Haskell.
Some of the code on this page uses features that we won’t see until later in the
semester, specifically $
, do
, and IO
. But it might be useful to learn
about testing before we learn about these Haskell features, and you can
write tests without having to know these details.
An example function to test
Let’s write and test a function to compute $n!$.
Here’s the Haskell code for factorial:
fact :: Integer -> Integer
fact 0 = 1
fact n = n * fact (n - 1)
To test this code, we’ll put it in a file called MyCode.hs
. Once we have that
code, we can manually test it using ghci. First we load the file:
$ ghci MyCode.hs
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( MyCode.hs, interpreted )
Ok, one module loaded.
*MyCode>
Now we can run some test cases:
*MyCode> fact 0
1
*MyCode> fact 1
1
*MyCode> fact 5
120
Great! Now we’re almost ready to write some actual testing code; but first let’s learn a little bit about modules.
Modules
It’s good practice to keep the “code under test” (e.g., fact
) separate from
the tests themselves. We’ll use modules to keep the code separate. A module
is just a way to organize code, which makes it easier for us to import and
export functionality in large programs.
Our code under test is actually already in a module, called Main
. We saw
that when we loaded MyCode.hs
in ghci:
$ ghci MyCode.hs
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( MyCode.hs, interpreted )
Ok, one module loaded.
When we don’t explicitly define a module for our file, Haskell automatically
defines a module called Main
for that file. We don’t need to define our own
module, but doing so will make our testing life easier.
To define our own module, we’ll put the following line of code at the top of the file:
module MyCode where
This line declares the MyCode
module in this file. In Haskell, a module name
must match its corresponding file name. A module makes it possible for other
files (e.g., our testing files) to import
our code under test.
That’s all we need to do! Here are the full contents of our MyCode.hs
file:
module MyCode where
fact :: Integer -> Integer
fact 0 = 1
fact n = n * fact (n - 1)
Now when we load this file in ghci, Haskell tells us the new module name:
$ ghci MyCode.hs
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling MyCode ( MyCode.hs, interpreted )
Ok, one module loaded.
*MyCode>
Nothing else has changed; we can still manually run test cases for our fact
function:
*MyCode> fact 0
1
*MyCode> fact 1
1
*MyCode> fact 5
120
That’s all we need to know about Haskell’s modules for now. If you’re interested in learning more about them, check out https://en.wikibooks.org/wiki/Haskell/Modules.
Tests
Let’s write some tests. To do so, we’ll first organize our code in a particular way.
Code organization.
We will use the following organization for our test code. We are not required to organize our code in this way, but doing so helps us take advantage of some useful, automated test-discovery features.
Here is the organization:
- The file with the code under test (i.e.,
MyCode.hs
) lives in the top-level directory. - All test files live in a subdirectory called
test
. - The name of each test file ends in
Spec.hs
.
So, for our factorial code, here’s our directory structure, where FactSpec.hs
will contain test code for the fact
function:
MyCode.hs
test/
FactSpec.hs
Defining Tests
We’ll start by writing one
unit test for fact
, which tests
that $0! = 1$. Inside test/FactSpec.hs
, we write the following:
module FactSpec where
import MyCode -- the code under test
import Test.Hspec -- for unit testing
{- Testing fact -}
spec :: Spec
spec =
describe "fact" $ do
context "fact 0" $
it "should be 1" $
fact 0 `shouldBe` 1
main :: IO ()
main = hspec spec
Let’s go through this code, piece-by-piece.
The first line declares a module for this file:
module FactSpec where
The next two lines import other modules:
import MyCode
import Test.Hspec
The first import
loads our code under test, which allows us to use fact
in
this file. The second import
loads a testing library called
hspec, which allows us to write tests.
Next comes the important part, a test:
spec :: Spec
spec =
describe "fact" $ do
context "fact 0" $
it "should be 1" $
fact 0 `shouldBe` 1
This code defines Spec
, i.e., a test. It probably looks a little weird, but
should be basically readable: it provides a description of the test (“fact 0
should be 1”) and the actual test:
fact 0 `shouldBe` 1
We’ll ignore any unusual Haskell syntax for now (it should make more sense as we learn more about Haskell). If you want to write your own tests, it’s pretty easy to copy/paste and modify this code.
At the bottom of the file, we have this code, which defines a main
function
that runs the test using the testing library’s hspec
function:
main :: IO ()
main = hspec spec
Now we can run our test!
Running Tests
To run our test, we can first load the test/FactSpec.hs
file in ghci:
From the top-level directory of our code (the one that contains MyCode.hs
), we run the
following command:
$ ghci test/FactSpec.hs
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
[1 of 2] Compiling MyCode ( MyCode.hs, interpreted )
[2 of 2] Compiling FactSpec ( test/FactSpec.hs, interpreted )
Ok, two modules loaded.
*FactSpec>
Next, we run the main
function, which itself runs the test:
*FactSpec> main
fact
fact 0
should be 1
Finished in 0.0010 seconds
1 example, 0 failures
Let’s add a couple more tests, to check that $1! = 1$ and $5! = 120$:
module FactSpec where
import MyCode -- the code under test
import Test.Hspec -- for unit testing
{- Testing fact -}
spec :: Spec
spec =
describe "fact" $ do
context "fact 0" $
it "should be 1" $
fact 0 `shouldBe` 1
context "fact 1" $
it "should be 1" $
fact 1 `shouldBe` 1
context "fact 5" $
it "should be 120" $
fact 5 `shouldBe` 120
main :: IO ()
main = hspec spec
To run these new tests, we need to reload the file in ghci:
*FactSpec> :l test/FactSpec
[1 of 2] Compiling MyCode ( MyCode.hs, interpreted )
[2 of 2] Compiling FactSpec ( test/FactSpec.hs, interpreted )
Ok, two modules loaded.
Now we can run =main= and see the results of our new tests:
*FactSpec> main
fact
fact 0
should be 1
fact 1
should be 1
fact 5
should be 120
Finished in 0.0011 seconds
3 examples, 0 failures
If one of our tests had failed, we could modify MyCode.hs
and reload the test
file. Similarly, if we want to write more tests, we could modify
test/FactSpec.hs
and reload it.
Property-based Testing
Now let’s explore a very cool Haskell testing library, one that lets us do property-based testing. In property-based testing, instead of defining a bunch of test cases, we describe a function’s behavior and let the testing library generate the test cases for us!
To see how this works, first, we will add a “plus one” function to MyCode.hs
:
mySuccessor :: Integer -> Integer
mySuccessor n = succ n
This function definition is silly; it just gives another name to the built-in succ
function. But our goal is not to write an interesting function; our goal is to write interesting
tests.
To test the mySuccessor
function, we create a file test/SuccessorSpec.hs
. If
we wanted, we could place unit tests in this file, like so:
module SuccessorSpec where
import MyCode -- the code under test
import Test.Hspec -- for unit testing
{- Testing mySuccessor -}
spec :: Spec
spec =
describe "MyCode.mySuccessor" $ do
-- Unit testing: test one input / output pair for this function
context "mySuccessor 0" $
it "should be 1" $
mySuccessor 0 `shouldBe` 1
main :: IO ()
main = hspec spec
And we can run the test like so:
$ ghci test/SuccessorSpec.hs
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
[1 of 2] Compiling MyCode ( MyCode.hs, interpreted )
[2 of 2] Compiling SuccessorSpec ( test/SuccessorSpec.hs, interpreted )
Ok, two modules loaded.
*SuccessorSpec> main
MyCode.mySuccessor
mySuccessor 0
should be 1
Finished in 0.0005 seconds
1 example, 0 failures
Property-based testing allows us to say: “The successor function should add 1 to its argument”. Here’s an update to the file that tests this “plus 1” property:
module SuccessorSpec where
import MyCode -- the code under test
import Test.Hspec -- for unit testing
import Test.QuickCheck -- for property-based testing
{- Testing mySuccessor -}
spec :: Spec
spec =
describe "MyCode.mySuccessor" $ do
-- Unit testing: test one input / output pair for this function
context "mySuccessor 0" $
it "should be 1" $
mySuccessor 0 `shouldBe` 1
-- Property-based testing: generate input / output pairs according
-- to a specification
context "when given a number n" $
it "should return the number n + 1" $ property $
\n -> mySuccessor n == n + 1
main :: IO ()
main = hspec spec
The line
import Test.QuickCheck
imports this quickcheck library, which lets us write property-based tests. Here is such a test:
context "when given a number n" $
it "should return the number n + 1" $ property $
\n -> mySuccessor n == n + 1
Notice the addition of property $
, followed by a function that expresses the
property: $\forall n . f(n) = n + 1$. When we run this test, the quickcheck
library will generate a bunch of possible inputs and check that the property
holds for each input. Let’s see that now:
*SuccessorSpec> :l test/SuccessorSpec
[1 of 2] Compiling MyCode ( MyCode.hs, interpreted )
[2 of 2] Compiling SuccessorSpec ( test/SuccessorSpec.hs, interpreted )
Ok, two modules loaded.
*SuccessorSpec> main
MyCode.mySuccessor
mySuccessor 0
should be 1
when given a number n
should return the number n + 1
+++ OK, passed 100 tests.
Finished in 0.0077 seconds
2 examples, 0 failures
Quickcheck generated 100 numbers n
and checked that mySuccessor n = n + 1
.
Multiple specs in the same test file
Sometimes, we might want to test multiple functions in the same file, and Haskell’s testing library makes that easy.
In MyCode.hs
, let’s add another “plus one function”:
mySuccessor' :: Integer -> Integer
mySuccessor' = (+ 1)
Now we have two different implementations of “plus one”: a function called
mySuccessor
and a function called mySuccessor'
. To test both functions in
the test/SuccessorSpec.hs
file, we write two distinct spec
s — one for
each function. Then, we combine the spec
s into a single one that we can run.
module SuccessorSpec where
import MyCode -- the code under test
import Test.Hspec -- for unit testing
import Test.QuickCheck -- for property-based testing
{- Testing mySuccessor -}
mySuccessorSpec :: Spec
mySuccessorSpec =
describe "MyCode.mySuccessor" $ do
-- Unit testing: test one input / output pair for this function
context "mySuccessor 0" $
it "should be 1" $
mySuccessor 0 `shouldBe` 1
-- Property-based testing: generate input / output pairs according
-- to a specification
context "when given a number n" $
it "should return the number n + 1" $ property $
\n -> mySuccessor n == n + 1
{- Testing mySuccessor' -}
mySuccessorSpec' :: Spec
mySuccessorSpec' =
describe "MyCode.mySuccessor'" $ do
-- Model testing: generate inputs and test against
-- a reference implementation (in this case, mySuccessor)
context "when given a number n" $
it "should return the same as mySuccessor n" $ property $
\n -> mySuccessor' n == mySuccessor n
spec :: Spec
spec = do
describe "mySuccessor" mySuccessorSpec
describe "mySuccessor'" mySuccessorSpec'
main :: IO ()
main = hspec spec
There are a few of things to call out here. First, each function under test gets
its own spec
.
Next, the spec
for mySuccessor'
uses mySuccessor
as a reference
implementation: the property says “for all inputs $n$, mySuccessor' n
should
give the same result as mySuccessor n
“.
Finally, the file combines the two spec
s together into a single spec
we can
run:
spec :: Spec
spec = do
describe "mySuccessor" mySuccessorSpec
describe "mySuccessor'" mySuccessorSpec'
main :: IO ()
main = hspec spec
To run the tests, we can load this file in ghci and run main
:
$ ghci test/SuccessorSpec.hs
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
[1 of 2] Compiling MyCode ( MyCode.hs, interpreted )
[2 of 2] Compiling SuccessorSpec ( test/SuccessorSpec.hs, interpreted )
Ok, two modules loaded.
*SuccessorSpec> main
mySuccessor
MyCode.mySuccessor
mySuccessor 0
should be 1
when given a number n
should return the number n + 1
+++ OK, passed 100 tests.
mySuccessor'
MyCode.mySuccessor'
when given a number n
should return the same as mySuccessor n
+++ OK, passed 100 tests.
Finished in 0.0030 seconds
3 examples, 0 failures
We can also run just one of the spec
s by passing it to the hspec
function:
*SuccessorSpec> hspec mySuccessorSpec
MyCode.mySuccessor
mySuccessor 0
should be 1
when given a number n
should return the number n + 1
+++ OK, passed 100 tests.
Finished in 0.0041 seconds
2 examples, 0 failures
Automated Test Discovery
We are starting to build up a good-sized testing suite for our code. Right now,
it consists of two files (test/FactSpec.hs
and test/SuccessorSpec.hs
), each
with multiple test cases. We can, of course, run each of these tests separately;
but it might be nice to run them all together. Additionally, as we add more code
and more tests, it would be nice to have a way to run all the tests.
Fortunately, with a little bit of magic, the Haskell testing library can discover all the tests we’ve written and automatically combine them into a single test suite.
Here’s how it works. First, we need to create a file test/Spec.hs
, with the
following contents:
{-# OPTIONS_GHC -F -pgmF hspec-discover #-}
Then, to load the tests into ghci, we load this file using the -itest
flag:
$ ghci -itest test/Spec.hs
GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help
[1 of 4] Compiling MyCode ( MyCode.hs, interpreted )
[2 of 4] Compiling FactSpec ( test/FactSpec.hs, interpreted )
[3 of 4] Compiling SuccessorSpec ( test/SuccessorSpec.hs, interpreted )
[4 of 4] Compiling Main ( test/Spec.hs, interpreted )
Ok, four modules loaded.
*Main>
(Note that we must use the -itest
flag when using automated test discovery. This flag tells Haskell where to look for the other test files, namely in the test
directory.)
Now, if we run main
, we’ll see the results of all our tests.
*Main> main
Fact
fact
fact 0
should be 1
fact 1
should be 1
fact 5
should be 120
Successor
mySuccessor
MyCode.mySuccessor
mySuccessor 0
should be 1
when given a number n
should return the number n + 1
+++ OK, passed 100 tests.
mySuccessor'
MyCode.mySuccessor'
when given a number n
should return the same as mySuccessor n
+++ OK, passed 100 tests.
Finished in 0.0042 seconds
6 examples, 0 failures
Cool!
The automated test discovery requires us to do the following things:
- Place our tests in the
test
subdirectory. - Make sure the name of each test file ends with
Spec.hs
. - Make sure each test file defines a variable
spec :: Spec
. -
Create a
test/Spec.hs
file that contains the “autodiscovery magic”:{-# OPTIONS_GHC -F -pgmF hspec-discover #-}
- Use the
-itest
flag when running the tests.
Try it for yourself!
The code for this page is available in our course GitHub, in the
example-tests
directory. Feel free to git clone
this code and play around with it.