module Main where import Data.Either (isRight) import Data.Hashable (Hashable) import qualified Data.Vector.Unboxed as Vector import Test.Framework (defaultMain, testGroup) import Test.Framework.Providers.HUnit (testCase) import Test.HUnit (assertBool, assertEqual) import qualified Data.PerfectHash.Construction as Construction import qualified Data.PerfectHash.Hashing as Hashing import Exercise (Atom (Atom)) import qualified Exercise testHashComputation :: String -> Int -> IO () testHashComputation key val = assertEqual error_message val computed_hash where error_message = unwords ["Incorrect hash computation of", key] computed_hash = Hashing.hash 0 key wordIndexTuples = [ ("apple", 1 :: Int) , ("banana", 2) , ("carrot", 3) ] intMapTuples :: [(Atom Int, Int)] intMapTuples = [ (Atom 1000, 1) , (Atom 5555, 2) , (Atom 9876, 3) ] testHashLookups :: (Show (f a), Show b, Eq b, Vector.Unbox b, Construction.Defaultable b, Foldable f, Hashing.ToNumeric a, Eq (f a), Hashable (f a)) => [(f a, b)] -> IO () testHashLookups word_index_tuples = assertBool "Perfect hash lookups failed to match the input" $ isRight test_result_either where lookup_table = Construction.createMinimalPerfectHash word_index_tuples test_result_either = Exercise.testLookups lookup_table word_index_tuples tests = [ testGroup "Hash computation" [ testCase "compute-hash1" $ testHashComputation "blarg" 3322346319 ] , testGroup "Hash lookups" [ testCase "word-lookups" $ testHashLookups wordIndexTuples , testCase "int-lookups" $ testHashLookups intMapTuples ] ] main = defaultMain tests