[Haskell-cafe] [newbie] How to test this function?

Donald Bruce Stewart dons at cse.unsw.edu.au
Thu Sep 21 00:52:38 EDT 2006


br1:
> I've written a function that looks similar to this one
  
> getList = find 5 where
>     find 0 = return []
>     find n = do
>       ch <- getChar
>       if ch `elem` ['a'..'e'] then do
>             tl <- find (n-1)
>             return (ch : tl) else
>           find n
  
> First, how do I fix the identation of the if then else?
  
getList = find 5
    where find 0 = return []
          find n = do
            ch <- getChar
            if ch `elem` ['a'..'e'] 
                then do tl <- find (n-1)
                        return (ch : tl) 
                else find n
  
> Second, I want to test this function, without hitting the filesystem.  In  
> C++ I would use a istringstream.  I couldn't find a function that returns  
> a Handle from a String.  The closer thing that may work that I could find  
> was making a pipe and convertind the file descriptor.  Can I simplify that  
> function to take it out of the IO monad?  How?  I thought about  
> getContents, but that eats all input.

Refactor! 
The reason your getList is hard to test, is that you're mixing side
effecting monadic code with pure computations. Let's untangle that, and
then test the the referentially transparent parts simply with
QuickCheck. And remember that since getContents uses lazy IO, it only
eats as much input as you ask it to.

So let's refactor this, partitioning off the side effecting IO code:

    getList :: IO [Char]
    getList = take5 `fmap` getContents -- a thin IO "skin"

    take5 :: [Char] -> [Char]
    take5 = take 5 . filter (`elem` ['a'..'e']) -- the actual worker

Now we can test the 'guts' of the algorithm, the take5 function, in
isolation. Let's use QuickCheck. First we need an Arbitrary instance for
the Char type -- this takes care of generating random Chars for us to
test with. I'll restrict it to a range of nice chars just for simplicity:

    import Data.Char
    import Test.QuickCheck

    instance Arbitrary Char where
        arbitrary     = choose ('\32', '\128')
        coarbitrary c = variant (ord c `rem` 4)

So now we can write some simple tests. 
An easy one, a [Char] is equal to itself:

    *A> quickCheck ((\s -> s == s) :: [Char] -> Bool)
    OK, passed 100 tests.

Reversing twice is the identity:
    *A> quickCheck ((\s -> (reverse.reverse) s == s) :: [Char] -> Bool)
    OK, passed 100 tests.

Ok, so what properties does take5 have? Well, for one, the length of the
string returned by take5 should be 5, no?

    *A> quickCheck (\s -> length (take5 s) == 5)
    Falsifiable, after 0 tests:
    ""

Ah, but what if the input file is small :) Thanks quickCheck. 

Let's modify that then:
    *A> quickCheck (\s -> length (take5 s) <= 5)
    OK, passed 100 tests.

Ok good.  You can probably come up with some more things to check for now.

-- Don


More information about the Haskell-Cafe mailing list