{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module BLAKE3
(
hash
, BIO.Digest
, hashKeyed
, BIO.Key
, BIO.key
, derive
, BIO.Context
, BIO.context
, BIO.Hasher
, hasher
, hasherKeyed
, update
, finalize
, BIO.KEY_LEN
, BIO.BLOCK_SIZE
, BIO.DEFAULT_DIGEST_LEN
)
where
import qualified Data.ByteArray as BA
import GHC.TypeLits
import System.IO.Unsafe (unsafeDupablePerformIO)
import qualified BLAKE3.IO as BIO
hash
:: forall len bin
. (KnownNat len, BA.ByteArrayAccess bin)
=> [bin]
-> BIO.Digest len
hash bins = unsafeDupablePerformIO $ do
fmap fst $ BIO.allocRetHasher $ \ph -> do
BIO.init ph
BIO.update ph bins
BIO.finalize ph
{-# NOINLINE hash #-}
hashKeyed
:: forall len bin
. (KnownNat len, BA.ByteArrayAccess bin)
=> BIO.Key
-> [bin]
-> BIO.Digest len
hashKeyed key0 bins = unsafeDupablePerformIO $ do
fmap fst $ BIO.allocRetHasher $ \ph -> do
BIO.initKeyed ph key0
BIO.update ph bins
BIO.finalize ph
{-# NOINLINE hashKeyed #-}
derive
:: forall len ikm
. (KnownNat len, BA.ByteArrayAccess ikm)
=> BIO.Context
-> [ikm]
-> BIO.Digest len
derive ctx ikms = unsafeDupablePerformIO $
fmap fst $ BIO.allocRetHasher $ \ph -> do
BIO.initDerive ph ctx
BIO.update ph ikms
BIO.finalize ph
{-# NOINLINE derive #-}
hasher :: BIO.Hasher
hasher = unsafeDupablePerformIO $
fmap snd $ BIO.allocRetHasher BIO.init
{-# NOINLINE hasher #-}
hasherKeyed :: BIO.Key -> BIO.Hasher
hasherKeyed key0 = unsafeDupablePerformIO $
fmap snd $ BIO.allocRetHasher $ \ph ->
BIO.initKeyed ph key0
{-# NOINLINE hasherKeyed #-}
update
:: forall bin
. BA.ByteArrayAccess bin
=> BIO.Hasher
-> [bin]
-> BIO.Hasher
update h0 bins = unsafeDupablePerformIO $ do
h1 <- BIO.copyHasher h0
BIO.withHasherInternal h1 $ \ph1 -> do
BIO.update ph1 bins
pure h1
{-# NOINLINE update #-}
finalize
:: forall len
. KnownNat len
=> BIO.Hasher
-> BIO.Digest len
finalize h0 = unsafeDupablePerformIO $ do
h1 <- BIO.copyHasher h0
BIO.withHasherInternal h1 $ \ph1 ->
BIO.finalize ph1
{-# NOINLINE finalize #-}