Functional Programming Unit Testing - Part 6

In the last installment in this series, we talked about separating the side effecting code from the pure functions.  I gave examples in both Haskell and F# to accomplish this goal, although with Haskell it’s more intuitive due to encapsulating the side effects within the IO monad.  This time, let’s cover how we can abstract the monadic code through the use of type classes.  Using the book, Real World Haskell, has opened up a lot of possibilities in this area.

 

Refactoring Again

I want to revisit our topic of refactoring that in the last post.  In this post and the next couple of posts, I want to explore additional areas with refactoring including the following:

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

In this post, let’s cover how we can abstract away the side effecting into a pure, controlled environment for testing.

 

Abstracting Towards Purity

In the Haskell world, there is both a blessing and a curse associated with the IO monad in how powerful it is.  The power comes from helping us avoid purity mistakes, but since there aren’t any grades of IO monads meaning to the level of what it can and cannot do, it could be a source of problems.  Taking an idea from the Real World Haskell book, we can not only tame the IO monad, but as well, hide it so that we could test our functions without actually causing any IO operations to take place.

In order to do this, we could specify a type class with specifies the interface we wish to expose to this monad.  If you’re not familiar with type classes, it’s a way that we can specify a set of functions that can have different implementations based upon the type given.  They could be mistaken for generic interfaces in the .NET world, but in fact they are quite different and a bit more powerful.  Let’s go ahead and define a type class for dealing with database interactions using HDBC and ODBC so that we could abstract away the IO and instead stub our return. 

-- file SqlAbstraction.hs
 
import Control.Monad
import Database.HDBC (SqlValue(..))
 
class Monad m => MonadConnection c m | m -> c where
  connectODBC :: String -> m c
  quickQuery' :: c -> String -> [SqlValue] -> m [[SqlValue]]
  run :: c -> String -> [SqlValue] -> m Integer
  commit :: c -> m()
  disconnect :: c -> m()

Now that we’ve defined what is allowed in our monadic abstraction, let’s stub out what some of these returns might be.  In order to do that, we need a monad that does nothing more than returns the original value, which is the Identity monad.  We can then implement an instance of the Identity monad on top of our abstraction such as the following.

-- file SqlAbstraction.hs

instance MonadConnection String Identity where
  connectODBC connString = return connString 
  quickQuery' conn cmd params =  
    return [[SqlInteger 1]]
  run conn cmd params = return
  commit conn = return () 
  disconnect conn = return ()

Now running our implementation of a given function that uses this monad is simple and would require nothing more than the following and yield a pure value.

ghci> :t runIdentity someFunction -- replace with a real function
runIdentity someFunction :: Bool
ghci> runIdentity someFunction
True

Now that we understand that we can stub out our return values from the monad instance, we could also look at what the real implementation might look like.

-- file SqlAbstraction.hs 

import qualified Database.HDBC 
import qualified Database.HDBC.ODBC 

instance MonadConnection Database.HDBC.ODBC.Connection IO where
  connectODBC = Database.HDBC.ODBC.connectODBC 
  quickQuery' = Database.HDBC.quickQuery' 
  run = Database.HDBC.run 
  commit = Database.HDBC.commit 
  disconnect = Database.HDBC.disconnect

We realize once I run the Identity version that because I’m getting a pure value with deterministic input based upon my stubs, I could write my tests in either HUnit, the xUnit style of testing, or just as well, I could use QuickCheck to verify the results.  In this instance, I’ll use HUnit to run through this because my inputs are well defined.

setSchema_ReturnSchema :: Test
setSchema_ReturnSchema = 
    TestCase $ assertEqual "Should get schema"
      (runIdentity $ setSchema "testConn" ["schema_version"])
    
setSchema_InsertSchema :: Test
setSchema_InsertSchema = 
    TestCase $ assertEqual "Should create schema with 0" 0
      (runIdentity $ setSchema "testConn" ["foobar"])

setSchema :: MonadConnection c m => c -> [String] -> m Int
setSchema conn tables =
    if "schema_version" `elem` tables
       then do r <- quickQuery' conn "SELECT version FROM schema_version" []
               case r of
                 [[x]] -> return (fromSql x)
                 x -> fail $ "Unexpected result in setSchema: " ++ show x
       else do run conn "CREATE TABLE schema_version (version INTEGER)" []
               run conn "INSERT INTO schema_version VALUES (0)" []
               commit conn
               return 0

Above is a simple implementation with the tests I defined to flush out the behavior of what setSchema should do.  The two cases define whether I already have a schema version or I don’t and act appropriately.  I can then run the tests to verify the behavior.

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

Not only could we test with stubs, but as well, we can capture which methods are called by logging all calls made to our MonadConnection functions through the use of the Writer monad.  This way, we can determine through examining our log afterwards which functions were called, and which were not.  First, we need to define even operations for all items that we care about.  Then we need to tell the Writer monad how to capture our events.  Let’s define how we might do that.

--file SqlAbstraction.hs

import Control.Monad.Writer

data Event = Open String
           | Query String String [SqlValue]
           | Run String String [SqlValue]
           | Commit String
           | Disconnect String
             deriving (Show, Eq)

newtype WriterIO a = W { runW :: Writer [Event] a}
  deriving (Monad, MonadWriter [Event])
  
runWriterIO :: WriterIO a -> (a, [Event])
runWriterIO = runWriter . runW

instance MonadConnection String WriterIO where
  connectODBC connString = tell [Open connString] >> return connString
  quickQuery' conn cmd params = 
    tell [Query conn cmd params] >> 
    return [[SqlInteger 1]
  run conn cmd params= tell [Run conn cmd params] >> return 0
  commit conn = tell [Commit conn]
  disconnect conn = tell [Disconnect conn]

In our MonadConnection instance, we are not only returning the values as before, but we are also using the tell function to log certain information about each function as they are called.  This way, when parsing the results of the Event list, we can determine whether our expectations were met.  Let’s write a simple example of how it actually works to capture the results.  Imagine this contrived example.

hasRecord :: MonadConnection c m => m Bool
hasRecord = do
  conn <- connectODBC "dsn=testdb"
  r <- quickQuery' conn "SELECT * FROM testdb WHERE id <= ?" 
    [toSql (2 :: Int)]
  disconnect conn
  return (length r > 0)
 

Running this example is as easy as above from the command line.  Let’s look at what it might produce:

ghci> :t runWriterIO hasRecord
runWriterIO hasRecord :: (Bool, [Event])
ghci> runWriterIO hasRecord
(True,[Open "dsn=testdb",Query "dsn=testdb" "SELECT * FROM testdb WHERE id <= ?"
[SqlInt32 2],Disconnect "dsn=testdb"])

What this was able to do was not only return the value, but also the logged events based upon what was called with the given arguments so that I may use any number of functions to analyze the event list.  Let’s write one last test against our setSchema function where we make sure that we’re committing the transaction if the schema_version table does not exist.  We recorded an action of Commit which should show up in our results, so we’re going to look for that as part of our test.

setSchema_CommitTrans :: Test
setSchema_CommitTrans =
    TestCase $ assertBool "Should commit transaction"
      (verifyCommit (runWriterIO $ setSchema "testConn" ["foobar"]))
      where verifyCommit res = let (r, a) = res in
                               Commit "testConn" `elem` a
 

Now that we’ve defined the test, we can run it to verify the result.

ghci> runTestTT setSchema_CommitTrans
Cases: 1  Tried: 1  Errors: 0  Failures: 0
Counts {cases = 1, tried = 1, errors = 0, failures = 0}
 

As you can see, we’re now able to detect when things happen in this monadic abstraction.  This leads to a lot of very interesting possibilities.  Especially if we take this example further to allow for some arbitrary IO instances using lifting and monad transformers.

The question is, are there any downsides?   There is a bit of work to stub out these samples, and once set, not easy to change for your given file.  But once you understand how to do this, testing in a pure environment becomes quite easy.  Taking lessons learned from the Haskell world, could we apply them to F#?

 

Monadic Abstraction in F#?

Understanding what we know about monads in Haskell, what I’d like is the opportunity to do the same with F# monads.  You may recall that that the standard for the monad in Haskell looks like the following.

class Monad m where
  (>>=) :: m a -> (a -> m b) -> m b
  (>>) :: m a -> m b -> m b
  return :: a -> m a
  fail :: String -> m a
 

As you can see, it’s using a typeclass to define the monad in that we could easily swap out instances.  In F#, monadic instances by a simple class which contains Delay, Bind and Return functions as the bare minimum defined such as the following outline:

type MonadBuilder =
  abstract member Bind : #Monad<'a> * ('a -> #Monad<'b>) -> #Monad<'b>
  abstract member Return : 'a -> #Monad<'a>
  abstract member Delay : (unit -> 'a)> 'a
 

Where #Monad is replaced with a concrete type of some sort such as ‘a list, ‘a option, Async<’a> and so on.  Using this as an outline, we can define such things as the Identity Monad such as the following.

type Identity<'a> = I of 'a 

type IdentityBuilder()
  member x.Bind(x:Identity<'a>, k:'a -> Identity<'b>)
    match x, k with 
    | I x, f -> f x  
  member x.Return(i:'a) : Identity<'a> = I i 
  member x.Delay(f) = f() 
   
let ident = new IdentityBuilder() 

let runIdentity = function
  | I x -> x
   
let iResult =  
  ident { let! f = I "foo" 
          return
        }
let result = runIdentity iResult
 

When we look at the above code, we realize that there really isn’t an easy way to abstract this in such a way that we could say, substitute an Identity monad for an async monad and expect it to continue with the code using the current way that F# sugars the monadic syntax.  It’s not to say it might not be able to get done, it’s just not worth the effort at this point using the existing sugaring.  Others have taken different angles such as such as with simple operators and template expansion, but in this case, I don’t think that’s enough to help.  Instead, it’s best to use the existing mocking frameworks that we already have to trace such behaviors.  The support of monads in F# at this juncture is limited by this fact that one monad cannot be substituted for another.  But this doesn’t stop me from enjoying monads in F#, but that’s for another post.

 

Conclusion

As you can see, monadic abstractions using type classes can be very useful in order to isolate side effects and test with pure values.  This gives us the ability to not only stub out our values, but also record the actions taken in a mock-ish way so that we observe our expectations.  Unfortunately, the way that F# monads were implemented does not lend itself to this operation, but my hope is that this is supported at some point.

There is still more to come in this series, including an exploration of cleaning up our code.  With such tools as HLint and others, we can better understand the language by some of the suggestions given.  And maybe you too could follow the Haskell Evolution, and maybe F# one in the future?



kick it on DotNetKicks.com

1 Comment

Comments have been disabled for this content.