{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_HADDOCK not-home #-}
module Bitcoin.Hash.GHC
( hash160
, hash256
, ripemd160
, sha256
, hmacSHA512
) where
import qualified Crypto.Hash as Hash
import qualified Crypto.MAC.HMAC as HMAC
import qualified Data.ByteArray as BA
import qualified Data.ByteString as B
hash160
:: B.ByteString
-> B.ByteString
{-# INLINE hash160 #-}
hash160 = BA.convert
. Hash.hash @(Hash.Digest Hash.SHA256) @Hash.RIPEMD160
. Hash.hash @B.ByteString @Hash.SHA256
hash256
:: B.ByteString
-> B.ByteString
{-# INLINE hash256 #-}
hash256 = BA.convert
. Hash.hash @(Hash.Digest Hash.SHA256) @Hash.SHA256
. Hash.hash @B.ByteString @Hash.SHA256
ripemd160
:: B.ByteString
-> B.ByteString
{-# INLINE ripemd160 #-}
ripemd160 = BA.convert
. Hash.hash @B.ByteString @Hash.RIPEMD160
sha256
:: B.ByteString
-> B.ByteString
{-# INLINE sha256 #-}
sha256 = BA.convert
. Hash.hash @B.ByteString @Hash.SHA256
hmacSHA512
:: B.ByteString
-> B.ByteString
-> B.ByteString
{-# INLINE hmacSHA512 #-}
hmacSHA512 k d = BA.convert (HMAC.hmac k d :: HMAC.HMAC Hash.SHA512)