{-# LINE 1 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} {-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-} {-# LINE 2 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} module Data.Digest.OpenSSL.AlternativeHMAC ( hmac , unsafeHMAC , showHMAC , CryptoHashFunction() , sha , sha1 , sha224 , sha256 , sha384 , sha512 ) where import Data.ByteString (ByteString) import qualified Data.ByteString as BS import Numeric (showHex) import System.IO.Unsafe import OpenSSL.EVP.Digest {-# LINE 24 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} {-# LINE 25 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} -- Types ----------------------------------------------------------------------- newtype CryptoHashFunction = CryptoHashFunction String -- | Name of the SHA digest, used by getDigestByName sha :: CryptoHashFunction sha = CryptoHashFunction ("SHA") {-# LINE 33 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} -- | Name of the SHA1 digest, used by getDigestByName sha1 :: CryptoHashFunction sha1 = CryptoHashFunction ("SHA1") {-# LINE 37 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} -- | Name of the SHA224 digest, used by getDigestByName sha224 :: CryptoHashFunction sha224 = CryptoHashFunction ("SHA224") {-# LINE 41 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} -- | Name of the SHA256 digest, used by getDigestByName sha256 :: CryptoHashFunction sha256 = CryptoHashFunction ("SHA256") {-# LINE 45 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} -- | Name of the SHA384 digest, used by getDigestByName sha384 :: CryptoHashFunction sha384 = CryptoHashFunction ("SHA384") {-# LINE 49 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} -- | Name of the SHA384 digest, used by getDigestByName sha512 :: CryptoHashFunction sha512 = CryptoHashFunction ("SHA512") {-# LINE 53 "src/Data/Digest/OpenSSL/AlternativeHMAC.hsc" #-} -- | Get the hex-string representation of an HMAC showHMAC :: ByteString -- ^ the HMAC -> String -- ^ the hex-string representation showHMAC bs = concatMap draw $ BS.unpack bs where draw :: (Integral a, Show a) => a -> String draw w = case showHex w [] of [x] -> ['0', x] x -> x -- | Wrapper/rendering function for hmac unsafeHMAC :: CryptoHashFunction -- ^ the name of the digest -> ByteString -- ^ the HMAC key -> ByteString -- ^ the data to be signed -> String -- ^ the hex-representation of the resulting HMAC unsafeHMAC h k i = unsafePerformIO (hmac h k i) hmac :: CryptoHashFunction -> ByteString -> ByteString -> IO String hmac (CryptoHashFunction s) k i = getDigestByName s >>= \ mbDigest -> case mbDigest of Nothing -> fail "no digest" Just d -> return $ showHMAC $ hmacBS d k i