{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module Crypto.Hash.KeccakSpec (spec) where import Crypto.Hash.Keccak (hashKeccak256) import Data.ByteArray (convert) import qualified Data.ByteString as BS import qualified Data.ByteString.Base16 as B16 import Test.Hspec import Test.QuickCheck -- Arbitrary instance for ByteString instance Arbitrary BS.ByteString where arbitrary = BS.pack <$> arbitrary spec :: Spec spec = do describe "hashKeccak256" $ do it "produces correct hash for empty string" $ do let result = convert (hashKeccak256 "") :: BS.ByteString Right expected = B16.decode "c5d2460186f7233c927e7db2dcc703c0e500b653ca82273b7bfad8045d85a470" result `shouldBe` expected it "produces correct hash for 'hello'" $ do let result = convert (hashKeccak256 "hello") :: BS.ByteString Right expected = B16.decode "1c8aff950685c2ed4bc3174f3472287b56d9517b9c948127319a09a7a36deac8" result `shouldBe` expected it "produces correct hash for 'Hello, World!'" $ do let result = convert (hashKeccak256 "Hello, World!") :: BS.ByteString Right expected = B16.decode "acaf3289d7b601cbd114fb36c4d29c85bbfd5e133f14cb355c3fd8d99367964f" result `shouldBe` expected it "always produces 32 bytes" $ property $ \(bs :: BS.ByteString) -> let result = convert (hashKeccak256 bs) :: BS.ByteString in BS.length result == 32 it "produces different hashes for different inputs" $ property $ \(x :: BS.ByteString, y :: BS.ByteString) -> x /= y ==> let hashX = convert (hashKeccak256 x) :: BS.ByteString hashY = convert (hashKeccak256 y) :: BS.ByteString in hashX /= hashY it "is deterministic" $ property $ \(bs :: BS.ByteString) -> let hash1 = convert (hashKeccak256 bs) :: BS.ByteString hash2 = convert (hashKeccak256 bs) :: BS.ByteString in hash1 == hash2