[Haskell-cafe] HUnit and table-driven tests

Dean Herington heringtonlacey at mindspring.com
Tue Aug 7 09:51:35 CEST 2012


At 4:30 PM -0700 8/5/12, Matthew wrote:
>On Sun, Aug 5, 2012 at 12:32 AM, Henk-Jan van Tuyl <hjgtuyl at chello.nl> wrote:
>>  On Sun, 05 Aug 2012 03:21:39 +0200, Matthew <wonderzombie at gmail.com> wrote:
>>
>>>  I've got a function which takes in two chars, describing a playing
>>>  card and a suit. An example would be 4C or TH for a 4 of Clubs or a
>>>  Ten of Hearts. I need to be able to compare the ranks of a card (e.g.
>>>  a King is 13), so a Card is a tuple of rank and suit. The function
>>>  which parses a Card is type String -> Maybe Card.
>>>
>>>  I'm writing unit tests for this using HUnit, and ideally I'd go with a
>>>  table-driven[1] approach, where each test case is a tuple of the input
>>>  and the expected output. (Possibly I could expand this to a triple, or
>>>  simply a list, to allow for an error message for each test case.) Then
>>>  all the test function has to do is run through each case and assert as
>>>  necessary. Example: [("TH", Just (Hearts, 10)), ("XH", Nothing)].
>>
>>
>>  A simple solution:
>>
>>>  parseCard :: String -> Maybe Card
>>>  parseCard string = <your function to test>
>>>  test :: Bool
>>>  test =  all testEqual [("TH", Just (Hearts, 10)), ("XH", Nothing)]
>>>      where
>>>        testEqual (input, output) = parseCard input == output
>>
>>
>>  For a description of 'all', see:
>> 
>>http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.html#v:all
>
>Thanks for the response. The one problem I have with this is that it
>will not be at all obvious which test case (or cases!) failed.
>
>That said, maybe I could do something similar, with a Writer? A passed
>test writes "", but a failed one writes a test-specific failure
>message. Then the test itself uses this string as the assert message.


Let HUnit tell you about the failing test cases.  Here's one way to do it.


import Test.HUnit
import Data.Char (isDigit)

data Suit = Spades | Hearts | Diamonds | Clubs
   deriving (Show, Read, Eq, Ord)
type Rank = Int  -- 2 .. 14 (jack=11, queen=12, king=13, ace=14)
type Card = (Suit, Rank)

parseCard :: String -> Maybe Card
parseCard [rankChar, suitChar] = do suit <- suitFrom suitChar; rank 
<- rankFrom rankChar; return (suit, rank)
parseCard _ = Nothing

suitFrom char = lookup char [('S', Spades), ('H', Hearts), ('D', 
Diamonds), ('C', Clubs)]

rankFrom dig | isDigit dig = let v = read [dig] in if v >= 2 then 
Just v else Nothing
rankFrom char = lookup char [('T', 10), ('J', 11), ('Q', 12), ('K', 
13), ('A', 14)]

makeTest :: (String, Maybe Card) -> Test
makeTest (string, result) = string ~: result ~=? parseCard string

tests = [("TH", Just (Hearts, 10)), ("XH", Nothing)]

main = (runTestTT . TestList . map makeTest) tests


Dean



More information about the Haskell-Cafe mailing list