Functional Programming Unit Testing - Part 5

In the last installment in this series, we talked about code coverage, what they are, and how you should use them.  I gave examples in both Haskell and F# to accomplish this goal.  One thing we've touched briefly in this conversation is around refactoring and cleaning up our code, and it’s about time we come back to that subject.

But, before we continue, let's get caught up to where we are today:

 

Refactoring

I want to revisit our topic of refactoring that I talked about with my foray into testing with HUnit.  In this post and the next couple of posts, I want to explore three different areas with refactoring including the following:

  • Keeping Things Pure
  • Monadic Isolation for Testing
  • Refactoring with frameworks (HLint, etc)

In this post, let’s cover keeping things pure and separating the side effecting code from our pure code. 

 

Keeping Things Pure

Let’s take a simple example of obtaining three odd numbers from a given stream handle.  Because side effects in Haskell are explicit, we have to be mindful of how we get our input.  This affects the signature of our function as it is no longer returning an integer list, but instead an IO integer list.  As I’ve stated in previous posts, you use QuickCheck for your pure code and xUnit frameworks for those with side effects, so in this case, we’d have to write an HUnit test for this function.  Let’s define the unit test which might satisfy those needs now.

-- RefactoringPure.hs
module RefactoringPure where

import System.IO
import Test.HUnit

test_getOddList :: Test
test_getOddList =
  TestCase $ do 
        inh <- openFile "test_getoddlist.txt" ReadMode
        results <- getOddList inh
        assertEqual "test should have three odds" [1,3,5] results

Then when we’re satisfied with writing this test, we then move onto the actual implementation in order to get this test to pass.  This involves some IO work as we noted before in order to take a given Handle and extract the results line by line.

-- RefactoringPure.hs
module RefactoringPure where

import System.IO

getOddList :: Handle -> IO [Int]    
getOddList h = find 3 where
     find 0 = return []
     find x = do
       ln <- hGetLine h
       let ln' = read ln::Int
       if odd ln' then do
             tl <- find (x - 1)
             return (ln' : tl) else
           find x
 

We can then verify our test using the GHCi by using the following to verify the results:

ghci> runTestTT $ TestList [test_getOddList]
Cases: 1  Tried: 1  Errors: 0  Failures: 0
Counts {cases = 1, tried = 1, errors = 0, failures = 0}

We get the test to pass, but this isn’t very satisfying.  The code looks enormously imperative, and to test all variations of odd numbers seems a bit daunting.  Dealing with IO issues can also lead to brittle tests and not testing the core domain of our application, our algorithms.  Instead, we’re putting too much effort into the IO part and not enough into where it matters most.  What' I’d prefer to write are QuickCheck property-based tests to define my behavior to cover all the variations of input to ensure the behavior of my functions. 

We need to untangle the pure code from the side effecting code.  We can rewrite the side effecting IO code to be just a simple thin layer on top of our algorithm.  From there, we can tease out the algorithm and write the tests the way they should be written in this situation.

-- RefactoringPure.hs
module RefactoringPure where

import Test.QuickCheck.Batch

prop_find3Odd_length :: [Int] -> Bool
prop_find3Odd_length xs =
  length (find3Odd xs) <= 3

prop_find3Odd_odds :: [Int] -> Bool
prop_find3Odd_odds =
  all odd . find3Odd
  
options = TestOptions
  { no_of_tests     = 200,
    length_of_tests = 1,
    debug_tests     = False
  }  
main :: IO ()  
main = do
  runTests "find3Odd" options
    [ run prop_find3Odd_length,
      run prop_find3Odd_odds
    ]
 

I’m much more satisfied with these property-based type checks instead, because they are less brittle and I’m now really testing the core logic of my domain.  The IO code is now nowhere to be found in these tests.  Now, let’s redo the functionality the way that it should be for this functionality that we want.

-- RefactoringPure.hs
module RefactoringPure where

import Control.Applicative
import System.IO

getOddList' :: Handle -> IO [Int]
getOddList' h = (find3Odd . map read . lines) <$> hGetContents h

find3Odd :: [Int] -> [Int]
find3Odd = take 3 . filter odd

Once the functionality has been implemented, we can now run our main function to determine the results of our property-based tests.

ghci> main
                 find3Odd : ..                               (400)

What we’ve been able to accomplish here is to separate the core domain of our application from the IO required to receive the input.  This is an important concept, no matter the paradigm between functional programming, object oriented programming or a hybrid approach of the two. 

I didn’t mention F# in this conversation as there is no enforced purity to be had, but the concepts still easily apply in this situation.  Below is a simple implementation of the Haskell code from above, in F# while isolating the side effecting code as a thin skin layer over top of our algorithm.

#light

namespace CodeBetter.Samples

module RefactoringPure =
  open FsCheck
  open FsCheckExtensions
  open Xunit 
  
  let odd n = n % 2 <> 0
  
  let find3Odd = List.take 3 << List.filter odd
  
  let getOddList (r:System.IO.StreamReader) =
     (find3Odd << List.map int << String.lines) (r.ReadToEnd())
  
  let prop_find3Odd_length xs =
    List.length (find3Odd xs) <= 3
    
  let prop_find3Odd_odds =
    List.for_all odd << find3Odd
  
  [<Fact>]
  let test_prop_find3Odd_length() =
    check config prop_find3Odd_length
    
  [<Fact>]
  let test_prop_find3Odd_odds() =
    check config prop_find3Odd_odds 

You may notice there are a few functions that don’t exist in the base F# libraries, and over time, I’ve implemented most of the base Haskell List functions in F# that didn’t already have an F# equivalent such as String.lines, List.take and so on.  I’ll cover what those functions are in a later post, because there are a few too many to mention at this point.  There are issues when going back and forth from strings to lists due to them being Seq<char> instead of char list, but that’s another post as well.

Back to the Haskell world for just a minute, there are other ways of approaching the problem including abstracting the monads and associated types through type classes so that we’re independent of any concrete implementation, which we’ll cover next time.

 

Conclusion

 

Refactoring is an important part of writing code when considering the Red/Green/Refactor paradigm from TDD.  By abstracting pure code from side effecting code, we can write effective tests using property-based checks using QuickCheck for our pure code, instead of more brittle tests which also include IO interaction.  Techniques that will be enumerated in this series will help write more robust and concise functional programming code.



kick it on DotNetKicks.com

No Comments