
I have a little binary search function and am trying to write tests for it in hunit. The below approach doesn't compile, because I'm attempting to build a list of tuples of different types, which isn't working for me. What's the appropriate way to do this test? http://gist.github.com/293031 import Test.HUnit import JoeBinarySearch -- Note: -- JoeBinarySearch.binary_search :: (Ord a) => [a] -> a -> Maybe Int assertions = [ ([1], 1, (Just 0)), ([1, 3], 1, (Just 0)), ([1, 3, 4], 4, (Just 2)), ([1,2,4,6,8,9,12,15,17,20], 17, (Just 8)), ([1,2,4,6,8,9,12,15,17,20], 20, (Just 9)), ("hello", 'l', (Just 2)), -- BOOM ([0.0, 1.5, 3.0], 3.0, (Just 2)), ([], 1, Nothing), ([1,3], 2, Nothing), ([1,4,6,8,9,12,15,17,20], 2, Nothing), ([1,4,6,8,9,12,15,17,20], 100, Nothing), ([1,4,6,8,9,12,15,17,20], (-100), Nothing)] test_list = TestList test_cases where test_cases = map test_func assertions test_func (lst, input, expected) = TestCase $ assert_equal' ( binary_search lst input ) expected assert_equal' = assertEqual "should equal" main :: IO () main = do runTestTT test_list print "DONE" -- Joe Van Dyk http://fixieconsulting.com

Am Dienstag 02 Februar 2010 22:18:50 schrieb Joe Van Dyk:
I have a little binary search function and am trying to write tests for it in hunit.
The below approach doesn't compile, because I'm attempting to build a list of tuples of different types, which isn't working for me.
What's the appropriate way to do this test?
QuickCheck, I'd say. Let that create more testcases than you could bother to write out. Anyway, for testing lists of different types, you'd need separate tests (properties/assertions). *But* you don't need that. Because the algorithm is general (works the same way for all types in Ord), the only way it could be correct on one type but not on another is if the Ord instance of one (or both) of the types is incorrect. So it's sufficient to test on [Int].
import Test.HUnit import JoeBinarySearch -- Note: -- JoeBinarySearch.binary_search :: (Ord a) => [a] -> a -> Maybe Int
assertions = [ ([1], 1, (Just 0)), ([1, 3], 1, (Just 0)), ([1, 3, 4], 4, (Just 2)), ([1,2,4,6,8,9,12,15,17,20], 17, (Just 8)), ([1,2,4,6,8,9,12,15,17,20], 20, (Just 9)), ("hello", 'l', (Just 2)), -- BOOM ([0.0, 1.5, 3.0], 3.0, (Just 2)), ([], 1, Nothing), ([1,3], 2, Nothing), ([1,4,6,8,9,12,15,17,20], 2, Nothing), ([1,4,6,8,9,12,15,17,20], 100, Nothing), ([1,4,6,8,9,12,15,17,20], (-100), Nothing)]
test_list = TestList test_cases where test_cases = map test_func assertions test_func (lst, input, expected) = TestCase $ assert_equal' ( binary_search lst input ) expected assert_equal' = assertEqual "should equal"
main :: IO () main = do runTestTT test_list print "DONE"

On Tue, Feb 2, 2010 at 1:34 PM, Daniel Fischer
Am Dienstag 02 Februar 2010 22:18:50 schrieb Joe Van Dyk:
I have a little binary search function and am trying to write tests for it in hunit.
The below approach doesn't compile, because I'm attempting to build a list of tuples of different types, which isn't working for me.
What's the appropriate way to do this test?
QuickCheck, I'd say. Let that create more testcases than you could bother to write out.
Anyway, for testing lists of different types, you'd need separate tests (properties/assertions).
*But* you don't need that. Because the algorithm is general (works the same way for all types in Ord), the only way it could be correct on one type but not on another is if the Ord instance of one (or both) of the types is incorrect.
So it's sufficient to test on [Int].
Good point, but I like to prove that to myself. :D Any chance anyone can show me how to write a QuickCheck test for this? Joe

Am Dienstag 02 Februar 2010 22:46:20 schrieb Joe Van Dyk:
On Tue, Feb 2, 2010 at 1:34 PM, Daniel Fischer
wrote: Am Dienstag 02 Februar 2010 22:18:50 schrieb Joe Van Dyk:
I have a little binary search function and am trying to write tests for it in hunit.
The below approach doesn't compile, because I'm attempting to build a list of tuples of different types, which isn't working for me.
What's the appropriate way to do this test?
QuickCheck, I'd say. Let that create more testcases than you could bother to write out.
Anyway, for testing lists of different types, you'd need separate tests (properties/assertions).
*But* you don't need that. Because the algorithm is general (works the same way for all types in Ord), the only way it could be correct on one type but not on another is if the Ord instance of one (or both) of the types is incorrect.
So it's sufficient to test on [Int].
Good point, but I like to prove that to myself. :D
Any chance anyone can show me how to write a QuickCheck test for this?
Joe
prop_binary_search :: Int -> [Int] -> Bool prop_binary_search x xs = let ys = sort xs in binary_search x ys == elemIndex x ys ghci> quickCheck prop_binary_search +++ OK, passed 100 tests.

Am Dienstag 02 Februar 2010 23:03:48 schrieb Daniel Fischer:
Am Dienstag 02 Februar 2010 22:46:20 schrieb Joe Van Dyk:
Any chance anyone can show me how to write a QuickCheck test for this?
Joe
prop_binary_search :: Int -> [Int] -> Bool prop_binary_search x xs = let ys = sort xs in binary_search x ys == elemIndex x ys
ghci> quickCheck prop_binary_search +++ OK, passed 100 tests.
Ah, but: ghci> quickCheckWith (stdArgs { maxSuccess = 10000, maxDiscard = 1000, maxSize = 2000 }) prop_binary_search *** Failed! Falsifiable (after 8007 tests and 3 shrinks): -1 [-1,-1] Okay, does that mean my function is wrong? In this case, no, my test was wrong. I intended binary_search to be used only on *strictly* ascending lists, so change the test to import Data.IntSet (fromList, toAscList) prop_binary_search :: Int -> [Int] -> Bool prop_binary_search x xs = let ys = toAscList (fromList xs) in binary_search x ys == elemIndex x ys Now: ghci> quickCheckWith (stdArgs { maxSuccess = 10000, maxDiscard = 1000, maxSize = 2000 }) prop_binary_search +++ OK, passed 10000 tests. or perhaps a different test: prop_binary_search_2 :: Int -> [Int] -> Bool prop_binary_search_2 x xs = let ys = sort xs in case binary_search x ys of Nothing -> x `notElem` ys Just k -> x == ys !! k

On Tue, Feb 2, 2010 at 1:18 PM, Joe Van Dyk
I have a little binary search function and am trying to write tests for it in hunit.
The below approach doesn't compile, because I'm attempting to build a list of tuples of different types, which isn't working for me.
What's the appropriate way to do this test?
import Test.HUnit import JoeBinarySearch -- Note: -- JoeBinarySearch.binary_search :: (Ord a) => [a] -> a -> Maybe Int
assertions = [ ([1], 1, (Just 0)), ([1, 3], 1, (Just 0)), ([1, 3, 4], 4, (Just 2)), ([1,2,4,6,8,9,12,15,17,20], 17, (Just 8)), ([1,2,4,6,8,9,12,15,17,20], 20, (Just 9)), ("hello", 'l', (Just 2)), -- BOOM ([0.0, 1.5, 3.0], 3.0, (Just 2)), ([], 1, Nothing), ([1,3], 2, Nothing), ([1,4,6,8,9,12,15,17,20], 2, Nothing), ([1,4,6,8,9,12,15,17,20], 100, Nothing), ([1,4,6,8,9,12,15,17,20], (-100), Nothing)]
test_list = TestList test_cases where test_cases = map test_func assertions test_func (lst, input, expected) = TestCase $ assert_equal' ( binary_search lst input ) expected assert_equal' = assertEqual "should equal"
main :: IO () main = do runTestTT test_list print "DONE"
I suppose I can live with this: build_test_case list element expected = test_case where test_case = TestCase assertion assertion = assertEqual "should equal" (binary_search list element) expected test_list = TestList [ build_test_case [1] 1 (Just 0), build_test_case [1, 3] 1 (Just 0), build_test_case [1, 3, 4] 4 (Just 2), build_test_case [1,2,4,6,8,9,12,15,17,20] 17 (Just 8), build_test_case [1,2,4,6,8,9,12,15,17,20] 20 (Just 9), build_test_case "hello" 'l' (Just 2), build_test_case [0.0, 1.5, 3.0] 3.0 (Just 2), build_test_case [] 1 Nothing, build_test_case [1,3] 2 Nothing, build_test_case [1,4,6,8,9,12,15,17,20] 2 Nothing, build_test_case [1,4,6,8,9,12,15,17,20] 100 Nothing, build_test_case [1,4,6,8,9,12,15,17,20] (-100) Nothing ] main :: IO () main = do runTestTT test_list print "DONE" But I assume there's a better way.
participants (2)
-
Daniel Fischer
-
Joe Van Dyk