{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE TypeFamilies #-}
module Cardano.Crypto.Hash.Keccak256
( Keccak256
)
where
import Cardano.Crypto.Hash.Class
import qualified "cryptonite" Crypto.Hash as H
import qualified Data.ByteArray as BA
data Keccak256
instance HashAlgorithm Keccak256 where
type SizeHash Keccak256 = 32
hashAlgorithmName :: proxy Keccak256 -> String
hashAlgorithmName proxy Keccak256
_ = String
"keccak256"
digest :: proxy Keccak256 -> ByteString -> ByteString
digest proxy Keccak256
_ = Digest Keccak_256 -> ByteString
convert (Digest Keccak_256 -> ByteString)
-> (ByteString -> Digest Keccak_256) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Digest Keccak_256
forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
ba -> Digest a
H.hash
convert :: H.Digest H.Keccak_256 -> ByteString
convert :: Digest Keccak_256 -> ByteString
convert = Digest Keccak_256 -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
BA.convert