Difference between revisions of "The Monad.Reader/Issue5/Software Testing With Haskell"

From HaskellWiki
Jump to navigation Jump to search
 
(→‎Everything Else: ln buddha, it seems to be more recent?)
 
(One intermediate revision by the same user not shown)
Line 1: Line 1:
 
=Software Testing With Haskell=
'''This article needs reformatting! Please help tidy it up.'''--[[User:WouterSwierstra|WouterSwierstra]] 14:27, 9 May 2008 (UTC)
 
 
:by ShaeErisson for The Monad.Reader Issue 5, Date: 2005-10-02T21:05:41Z
   
 
The two most commonly used libraries for testing software with Haskell are [[HUnit]] and [[QuickCheck]]. This article will shortly describe the two different approaches and show some demonstration code.
= Software Testing With Haskell =
 
''by ShaeErisson for The Monad.Reader Issue 5''
 
[[BR]]
 
''[[Date(2005-10-02T21:05:41Z)]]''
 
   
 
Both HUnit and QuickCheck are included with GHC 6.4.1 under the module names of Test.HUnit and Test.QuickCheck
'''Abstract.'''
 
   
 
==HUnit==
The two most commonly used libraries for testing software with Haskell are HUnit and QuickCheck. This article will shortly describe the two different approaches and show some demonstration code.
 
 
HUnit was written by Dean Herington and is available on SourceForge at http://hunit.sourceforge.net/ .
 
Both HUnit and QuickCheck are included with GHC 6.4.1 under the module names of Test.HUnit and Test.QuickCheck
 
= HUnit =
 
HUnit was written by Dean Herington and is available on sourceforge at http://hunit.sourceforge.net/ .
 
   
If you've ever used the [http://en.wikipedia.org/wiki/XUnit xUnit] framework in other programming languages, HUnit will feel familiar. The [http://hunit.sourceforge.net/HUnit-1.0/Guide.html User's Guide] includes a 'getting started' started section, and there are a thousand introductions to various flavors of the xUnit framework, so we'll mention HUnit only briefly.
+
If you've ever used the [http://en.wikipedia.org/wiki/XUnit xUnit] framework in other programming languages, HUnit will feel familiar. The [http://hunit.sourceforge.net/HUnit-1.0/Guide.html User's Guide] includes a 'getting started' started section, and there are a thousand introductions to various flavors of the xUnit framework, so we'll mention HUnit only briefly.
   
 
From the user's guide:
 
From the user's guide:
   
"Tests are specified compositionally. [http://hunit.sourceforge.net/HUnit-1.0/Guide.html#Assertions Assertions] are combined to make a [http://hunit.sourceforge.net/HUnit-1.0/Guide.html#TestCase test case], and test cases are combined into [http://hunit.sourceforge.net/HUnit-1.0/Guide.html#Tests tests]."
+
<blockquote>"Tests are specified compositionally. [http://hunit.sourceforge.net/HUnit-1.0/Guide.html#Assertions Assertions] are combined to make a [http://hunit.sourceforge.net/HUnit-1.0/Guide.html#TestCase test case], and test cases are combined into [http://hunit.sourceforge.net/HUnit-1.0/Guide.html#Tests tests]."</blockquote>
   
 
Here's a short demo:
 
Here's a short demo:
{{{#!syntax haskell
+
<haskell>
 
module ProtoHunit where
 
module ProtoHunit where
   
 
import Test.HUnit
 
import Test.HUnit
import Test.HUnit
+
import Test.HUnit
   
 
testList = TestList -- construct a TestList from a list of type TestCase
 
testList = TestList -- construct a TestList from a list of type TestCase
[TestCase $ -- construct a TestCase from an assertion
+
[TestCase $ -- construct a TestCase from an assertion
assertEqual "description" 2 (1 + 1) -- construct an assertion from a descriptive string, an expected result, and something to execute
+
assertEqual "description" 2 (1 + 1) -- construct an assertion from a descriptive string, an expected result, and something to execute
  +
]
]
 
   
 
t = runTestTT testList
 
t = runTestTT testList
  +
</haskell>
}}}
 
   
= QuickCheck =
+
==QuickCheck==
 
QuickCheck was written by Koen Claessan and John Hughes, and is available from Chalmers at http://www.cs.chalmers.se/~rjmh/QuickCheck/ .
 
QuickCheck was written by Koen Claessan and John Hughes, and is available from Chalmers at http://www.cs.chalmers.se/~rjmh/QuickCheck/ .
   
QuickCheck takes a dramatically different approach to software testing. The programmer specifies a property that the code should follow, and the QuickCheck library generates random values and checks to see if the property always holds.
+
QuickCheck takes a dramatically different approach to software testing. The programmer specifies a property that the code should follow, and the QuickCheck library generates random values and checks to see if the property always holds.
   
 
Some demonstration properties are given below.
 
Some demonstration properties are given below.
{{{#!syntax haskell
+
<haskell>
 
module ProtoQuickCheck where
 
module ProtoQuickCheck where
 
import Test.QuickCheck
 
import Test.QuickCheck
   
 
-- this succeeds in one case of the input.
 
-- this succeeds in one case of the input.
prop_Fail :: Int -> Bool
+
prop_Fail :: Int -> Bool
prop_Fail x =
+
prop_Fail x =
x == 1
+
x == 1
   
 
-- this succeeds in three cases of the input.
 
-- this succeeds in three cases of the input.
 
prop_RevUnit :: [Int] -> Bool
 
prop_RevUnit :: [Int] -> Bool
prop_RevUnit x =
+
prop_RevUnit x =
reverse x == x
+
reverse x == x
   
 
-- what's wrong with this picture?
 
-- what's wrong with this picture?
 
prop_RevUnitConfusion :: [Int] -> Bool
 
prop_RevUnitConfusion :: [Int] -> Bool
prop_RevUnitConfusion x =
+
prop_RevUnitConfusion x =
reverse [x] == [x]
+
reverse [x] == [x]
   
 
-- do you see a bug?
 
-- do you see a bug?
 
prop_RevApp :: [Int] -> [Int] -> Bool
 
prop_RevApp :: [Int] -> [Int] -> Bool
prop_RevApp xs ys =
+
prop_RevApp xs ys =
reverse (xs ++ ys) == reverse xs ++ reverse ys
+
reverse (xs ++ ys) == reverse xs ++ reverse ys
   
 
prop_RevRev :: [Int] -> Bool
 
prop_RevRev :: [Int] -> Bool
prop_RevRev xs =
+
prop_RevRev xs =
reverse (reverse xs) == xs
+
reverse (reverse xs) == xs
   
 
(f === g) x = f x == g x
 
(f === g) x = f x == g x
   
prop_CompAssoc :: (Int -> Int) -> (Int -> Int) -> (Int -> Int) -> Int -> Bool
+
prop_CompAssoc :: (Int -> Int) -> (Int -> Int) -> (Int -> Int) -> Int -> Bool
 
prop_CompAssoc f g h = (f . (g . h)) === ((f . g) . h)
 
prop_CompAssoc f g h = (f . (g . h)) === ((f . g) . h)
   
prop_CompCommut :: (Int -> Int) -> (Int -> Int) -> Int -> Bool
+
prop_CompCommut :: (Int -> Int) -> (Int -> Int) -> Int -> Bool
 
prop_CompCommut f g = (f . g) === (g . f)
 
prop_CompCommut f g = (f . g) === (g . f)
   
Line 80: Line 75:
 
-- means filter inputs by that condition
 
-- means filter inputs by that condition
 
-- below an x and y are only accepted if x is less than or equal to y
 
-- below an x and y are only accepted if x is less than or equal to y
prop_MaxLe :: Int -> Int -> Property
+
prop_MaxLe :: Int -> Int -> Property
 
prop_MaxLe x y = x <= y ==> max x y == y
 
prop_MaxLe x y = x <= y ==> max x y == y
   
 
instance Show (a -> b) where show _ = "<<function>>"
 
instance Show (a -> b) where show _ = "<<function>>"
   
  +
</haskell>
}}}
 
To test one of these properties, load the source into ghci and run "quickCheck prop_Fail". One possible response is:
+
To test one of these properties, load the source into ghci and run <tt>quickCheck prop_Fail</tt>. One possible response is:
  +
<haskell>
{{{
 
 
Falsifiable, after 0 tests:
 
Falsifiable, after 0 tests:
 
-1
 
-1
  +
</haskell>
}}}
 
Since the type signature of prop_Fail is {{{Int -> Bool}}} QuickCheck generated an Int value and checked to see if the property held true. Since the value -1 is not equal to 1, the property is false.
+
Since the type signature of prop_Fail is <haskell>Int -> Bool</haskell> QuickCheck generated an Int value and checked to see if the property held true. Since the value -1 is not equal to 1, the property is false.
   
= Everything Else =
+
==Everything Else==
The Haskell wiki has information on [http://www.haskell.org/hawiki/HaskellMode one button unit testing] with emacs' haskell-mode.
+
The Haskell wiki has information on [[haskell-mode|one button unit testing]] with the emacs haskell-mode.
   
 
Other libraries and applications that deal with software testing in Haskell are mentioned below, but are beyond the scope of this short introduction.
 
Other libraries and applications that deal with software testing in Haskell are mentioned below, but are beyond the scope of this short introduction.
* [http://www.haskell.org/hat/ Hat] The Haskell Tracer.
+
* [[Hat]] The Haskell Tracer.
* [http://www.cs.mu.oz.au/~bjpop/plargleflarp/ Plargeflarp] (declarative debugger formerly known as buddha)
+
* [http://www.cs.mu.oz.au/~bjpop/plargleflarp/ Plargeflarp] (declarative debugger sometimes known as [http://www.cs.mu.oz.au/~bjpop/buddha/ Buddha])
* [http://www.cse.ogi.edu/~hallgren/Programatica/ Programatica] is a collection of tools, that include the ability to specify inline 'certificates'. 'Certificates' are tests, they can be static unit tests, QuickCheck properties, or automated proofs.
+
* [http://www.cse.ogi.edu/~hallgren/Programatica/ Programatica] is a collection of tools, that include the ability to specify inline 'certificates'. 'Certificates' are tests, they can be static unit tests, QuickCheck properties, or automated proofs.
  +
----
 
  +
[[Category:Article]]
CategoryArticle
 

Latest revision as of 03:10, 10 May 2008

Software Testing With Haskell

by ShaeErisson for The Monad.Reader Issue 5, Date: 2005-10-02T21:05:41Z

The two most commonly used libraries for testing software with Haskell are HUnit and QuickCheck. This article will shortly describe the two different approaches and show some demonstration code.

Both HUnit and QuickCheck are included with GHC 6.4.1 under the module names of Test.HUnit and Test.QuickCheck

HUnit

HUnit was written by Dean Herington and is available on SourceForge at http://hunit.sourceforge.net/ .

If you've ever used the xUnit framework in other programming languages, HUnit will feel familiar. The User's Guide includes a 'getting started' started section, and there are a thousand introductions to various flavors of the xUnit framework, so we'll mention HUnit only briefly.

From the user's guide:

"Tests are specified compositionally. Assertions are combined to make a test case, and test cases are combined into tests."

Here's a short demo:

module ProtoHunit where

import Test.HUnit
import Test.HUnit

testList = TestList -- construct a TestList from a list of type TestCase
 [TestCase $ -- construct a TestCase from an assertion
 assertEqual "description" 2 (1 + 1) -- construct an assertion from a descriptive string, an expected result, and something to execute
 ]

t = runTestTT testList

QuickCheck

QuickCheck was written by Koen Claessan and John Hughes, and is available from Chalmers at http://www.cs.chalmers.se/~rjmh/QuickCheck/ .

QuickCheck takes a dramatically different approach to software testing. The programmer specifies a property that the code should follow, and the QuickCheck library generates random values and checks to see if the property always holds.

Some demonstration properties are given below.

module ProtoQuickCheck where
import Test.QuickCheck

-- this succeeds in one case of the input.
prop_Fail :: Int -> Bool
prop_Fail x =
 x == 1

-- this succeeds in three cases of the input.
prop_RevUnit :: [Int] -> Bool
prop_RevUnit x =
 reverse x == x

-- what's wrong with this picture?
prop_RevUnitConfusion :: [Int] -> Bool
prop_RevUnitConfusion x =
 reverse [x] == [x]

-- do you see a bug?
prop_RevApp :: [Int] -> [Int] -> Bool
prop_RevApp xs ys =
 reverse (xs ++ ys) == reverse xs ++ reverse ys

prop_RevRev :: [Int] -> Bool
prop_RevRev xs =
 reverse (reverse xs) == xs

(f === g) x = f x == g x

prop_CompAssoc :: (Int -> Int) -> (Int -> Int) -> (Int -> Int) -> Int -> Bool
prop_CompAssoc f g h = (f . (g . h)) === ((f . g) . h)

prop_CompCommut :: (Int -> Int) -> (Int -> Int) -> Int -> Bool
prop_CompCommut f g = (f . g) === (g . f)

-- this operator ==>
-- means filter inputs by that condition
-- below an x and y are only accepted if x is less than or equal to y
prop_MaxLe :: Int -> Int -> Property
prop_MaxLe x y = x <= y ==> max x y == y

instance Show (a -> b) where show _ = "<<function>>"

To test one of these properties, load the source into ghci and run quickCheck prop_Fail. One possible response is:

Falsifiable, after 0 tests:
-1
Since the type signature of prop_Fail is
Int -> Bool
QuickCheck generated an Int value and checked to see if the property held true. Since the value -1 is not equal to 1, the property is false.

Everything Else

The Haskell wiki has information on one button unit testing with the emacs haskell-mode.

Other libraries and applications that deal with software testing in Haskell are mentioned below, but are beyond the scope of this short introduction.

  • Hat The Haskell Tracer.
  • Plargeflarp (declarative debugger sometimes known as Buddha)
  • Programatica is a collection of tools, that include the ability to specify inline 'certificates'. 'Certificates' are tests, they can be static unit tests, QuickCheck properties, or automated proofs.