{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

-- | Haskell bindings to the fast [official BLAKE3 hashing
-- implementation in assembly and C](https://github.com/BLAKE3-team/BLAKE3).
-- With support for AVX-512, AVX2 and SSE 4.1.
--
-- The original assembly and C implementation is released into the public domain with CC0 1.0.
-- Alternatively, it is licensed under the Apache License 2.0, copyright of Jack
-- O'Connor and Samuel Neves. See its [LICENSE](https://github.com/BLAKE3-team/BLAKE3/blob/88dcee7005be962a81516f7863e70009d9caa2c9/LICENSE)
-- for details.
--
-- This Haskell library is the copyright of Renzo Carbonara,
-- licensed under the terms of
-- the [Apache License 2.0](https://github.com/k0001/hs-blake3/blob/master/blake3/LICENSE).
module BLAKE3
  ( -- * Hashing
    hash
  , BIO.Digest
    -- * Keyed hashing
  , hashKeyed
  , BIO.Key
  , BIO.key
    -- * Key derivation
  , derive
  , BIO.Context
  , BIO.context
    -- * Incremental hashing
  , BIO.Hasher
  , hasher
  , hasherKeyed
  , update
  , finalize
    -- * Constants
  , 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

--------------------------------------------------------------------------------

-- | BLAKE3 hashing.
--
-- For incremental hashing, see 'hasher', 'update' and 'finalize':
--
-- @
-- 'hash' = 'finalize' '.' 'update' 'hasher'
-- @
hash
  :: forall len bin
  .  (KnownNat len, BA.ByteArrayAccess bin)
  => [bin]           -- ^ Data to hash.
  -> BIO.Digest len  -- ^ Default digest length is 'BIO.DEFAULT_DIGEST_LEN'.
hash :: [bin] -> Digest len
hash bins :: [bin]
bins = IO (Digest len) -> Digest len
forall a. IO a -> a
unsafeDupablePerformIO (IO (Digest len) -> Digest len) -> IO (Digest len) -> Digest len
forall a b. (a -> b) -> a -> b
$ do
  ((Digest len, Hasher) -> Digest len)
-> IO (Digest len, Hasher) -> IO (Digest len)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Digest len, Hasher) -> Digest len
forall a b. (a, b) -> a
fst (IO (Digest len, Hasher) -> IO (Digest len))
-> IO (Digest len, Hasher) -> IO (Digest len)
forall a b. (a -> b) -> a -> b
$ (Ptr HasherInternal -> IO (Digest len)) -> IO (Digest len, Hasher)
forall a. (Ptr HasherInternal -> IO a) -> IO (a, Hasher)
BIO.allocRetHasher ((Ptr HasherInternal -> IO (Digest len))
 -> IO (Digest len, Hasher))
-> (Ptr HasherInternal -> IO (Digest len))
-> IO (Digest len, Hasher)
forall a b. (a -> b) -> a -> b
$ \ph :: Ptr HasherInternal
ph -> do
    Ptr HasherInternal -> IO ()
BIO.init Ptr HasherInternal
ph
    Ptr HasherInternal -> [bin] -> IO ()
forall bin.
ByteArrayAccess bin =>
Ptr HasherInternal -> [bin] -> IO ()
BIO.update Ptr HasherInternal
ph [bin]
bins
    Ptr HasherInternal -> IO (Digest len)
forall (len :: Nat).
KnownNat len =>
Ptr HasherInternal -> IO (Digest len)
BIO.finalize Ptr HasherInternal
ph
{-# NOINLINE hash #-}

-- | BLAKE3 hashing with a 'BIO.Key'.
--
-- For incremental hashing, see 'hasherKeyed', 'update' and 'finalize':
--
-- @
-- 'hashKeyed' key = 'finalize' '.' 'update' ('hasherKeyed' key)
-- @
hashKeyed
  :: forall len bin
  .  (KnownNat len, BA.ByteArrayAccess bin)
  => BIO.Key
  -> [bin]           -- ^ Data to hash.
  -> BIO.Digest len  -- ^ Default digest length is 'BIO.DEFAULT_DIGEST_LEN'.
hashKeyed :: Key -> [bin] -> Digest len
hashKeyed key0 :: Key
key0 bins :: [bin]
bins = IO (Digest len) -> Digest len
forall a. IO a -> a
unsafeDupablePerformIO (IO (Digest len) -> Digest len) -> IO (Digest len) -> Digest len
forall a b. (a -> b) -> a -> b
$ do
  ((Digest len, Hasher) -> Digest len)
-> IO (Digest len, Hasher) -> IO (Digest len)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Digest len, Hasher) -> Digest len
forall a b. (a, b) -> a
fst (IO (Digest len, Hasher) -> IO (Digest len))
-> IO (Digest len, Hasher) -> IO (Digest len)
forall a b. (a -> b) -> a -> b
$ (Ptr HasherInternal -> IO (Digest len)) -> IO (Digest len, Hasher)
forall a. (Ptr HasherInternal -> IO a) -> IO (a, Hasher)
BIO.allocRetHasher ((Ptr HasherInternal -> IO (Digest len))
 -> IO (Digest len, Hasher))
-> (Ptr HasherInternal -> IO (Digest len))
-> IO (Digest len, Hasher)
forall a b. (a -> b) -> a -> b
$ \ph :: Ptr HasherInternal
ph -> do
    Ptr HasherInternal -> Key -> IO ()
BIO.initKeyed Ptr HasherInternal
ph Key
key0
    Ptr HasherInternal -> [bin] -> IO ()
forall bin.
ByteArrayAccess bin =>
Ptr HasherInternal -> [bin] -> IO ()
BIO.update Ptr HasherInternal
ph [bin]
bins
    Ptr HasherInternal -> IO (Digest len)
forall (len :: Nat).
KnownNat len =>
Ptr HasherInternal -> IO (Digest len)
BIO.finalize Ptr HasherInternal
ph
{-# NOINLINE hashKeyed #-}

-- | BLAKE3 key derivation.
derive
  :: forall len ikm
  .  (KnownNat len, BA.ByteArrayAccess ikm)
  => BIO.Context
  -> [ikm]  -- ^ Input key material.
  -> BIO.Digest len  -- ^ Default digest length is 'BIO.DEFAULT_DIGEST_LEN'.
derive :: Context -> [ikm] -> Digest len
derive ctx :: Context
ctx ikms :: [ikm]
ikms = IO (Digest len) -> Digest len
forall a. IO a -> a
unsafeDupablePerformIO (IO (Digest len) -> Digest len) -> IO (Digest len) -> Digest len
forall a b. (a -> b) -> a -> b
$
  ((Digest len, Hasher) -> Digest len)
-> IO (Digest len, Hasher) -> IO (Digest len)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Digest len, Hasher) -> Digest len
forall a b. (a, b) -> a
fst (IO (Digest len, Hasher) -> IO (Digest len))
-> IO (Digest len, Hasher) -> IO (Digest len)
forall a b. (a -> b) -> a -> b
$ (Ptr HasherInternal -> IO (Digest len)) -> IO (Digest len, Hasher)
forall a. (Ptr HasherInternal -> IO a) -> IO (a, Hasher)
BIO.allocRetHasher ((Ptr HasherInternal -> IO (Digest len))
 -> IO (Digest len, Hasher))
-> (Ptr HasherInternal -> IO (Digest len))
-> IO (Digest len, Hasher)
forall a b. (a -> b) -> a -> b
$ \ph :: Ptr HasherInternal
ph -> do
    Ptr HasherInternal -> Context -> IO ()
BIO.initDerive Ptr HasherInternal
ph Context
ctx
    Ptr HasherInternal -> [ikm] -> IO ()
forall bin.
ByteArrayAccess bin =>
Ptr HasherInternal -> [bin] -> IO ()
BIO.update Ptr HasherInternal
ph [ikm]
ikms
    Ptr HasherInternal -> IO (Digest len)
forall (len :: Nat).
KnownNat len =>
Ptr HasherInternal -> IO (Digest len)
BIO.finalize Ptr HasherInternal
ph
{-# NOINLINE derive #-}

-- | Initial 'BIO.Hasher' for incremental hashing.
hasher :: BIO.Hasher -- ^
hasher :: Hasher
hasher = IO Hasher -> Hasher
forall a. IO a -> a
unsafeDupablePerformIO (IO Hasher -> Hasher) -> IO Hasher -> Hasher
forall a b. (a -> b) -> a -> b
$
  (((), Hasher) -> Hasher) -> IO ((), Hasher) -> IO Hasher
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((), Hasher) -> Hasher
forall a b. (a, b) -> b
snd (IO ((), Hasher) -> IO Hasher) -> IO ((), Hasher) -> IO Hasher
forall a b. (a -> b) -> a -> b
$ (Ptr HasherInternal -> IO ()) -> IO ((), Hasher)
forall a. (Ptr HasherInternal -> IO a) -> IO (a, Hasher)
BIO.allocRetHasher Ptr HasherInternal -> IO ()
BIO.init
{-# NOINLINE hasher #-}

-- | Initial 'BIO.Hasher' for incremental /keyed/ hashing.
hasherKeyed :: BIO.Key -> BIO.Hasher -- ^
hasherKeyed :: Key -> Hasher
hasherKeyed key0 :: Key
key0 = IO Hasher -> Hasher
forall a. IO a -> a
unsafeDupablePerformIO (IO Hasher -> Hasher) -> IO Hasher -> Hasher
forall a b. (a -> b) -> a -> b
$
  (((), Hasher) -> Hasher) -> IO ((), Hasher) -> IO Hasher
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((), Hasher) -> Hasher
forall a b. (a, b) -> b
snd (IO ((), Hasher) -> IO Hasher) -> IO ((), Hasher) -> IO Hasher
forall a b. (a -> b) -> a -> b
$ (Ptr HasherInternal -> IO ()) -> IO ((), Hasher)
forall a. (Ptr HasherInternal -> IO a) -> IO (a, Hasher)
BIO.allocRetHasher ((Ptr HasherInternal -> IO ()) -> IO ((), Hasher))
-> (Ptr HasherInternal -> IO ()) -> IO ((), Hasher)
forall a b. (a -> b) -> a -> b
$ \ph :: Ptr HasherInternal
ph ->
  Ptr HasherInternal -> Key -> IO ()
BIO.initKeyed Ptr HasherInternal
ph Key
key0
{-# NOINLINE hasherKeyed #-}

-- | Update 'BIO.Hasher' with new data.
update
  :: forall bin
  .  BA.ByteArrayAccess bin
  => BIO.Hasher
  -> [bin]  -- ^ New data to hash.
  -> BIO.Hasher
update :: Hasher -> [bin] -> Hasher
update h0 :: Hasher
h0 bins :: [bin]
bins = IO Hasher -> Hasher
forall a. IO a -> a
unsafeDupablePerformIO (IO Hasher -> Hasher) -> IO Hasher -> Hasher
forall a b. (a -> b) -> a -> b
$ do
  Hasher
h1 <- Hasher -> IO Hasher
BIO.copyHasher Hasher
h0
  Hasher -> (Ptr HasherInternal -> IO Hasher) -> IO Hasher
forall a. Hasher -> (Ptr HasherInternal -> IO a) -> IO a
BIO.withHasherInternal Hasher
h1 ((Ptr HasherInternal -> IO Hasher) -> IO Hasher)
-> (Ptr HasherInternal -> IO Hasher) -> IO Hasher
forall a b. (a -> b) -> a -> b
$ \ph1 :: Ptr HasherInternal
ph1 -> do
    Ptr HasherInternal -> [bin] -> IO ()
forall bin.
ByteArrayAccess bin =>
Ptr HasherInternal -> [bin] -> IO ()
BIO.update Ptr HasherInternal
ph1 [bin]
bins
    Hasher -> IO Hasher
forall (f :: * -> *) a. Applicative f => a -> f a
pure Hasher
h1
{-# NOINLINE update #-}

-- | Finish hashing and obtain a 'BIO.Digest' of the specified @len@gth.
finalize
  :: forall len
  .  KnownNat len
  => BIO.Hasher -- ^
  -> BIO.Digest len
finalize :: Hasher -> Digest len
finalize h0 :: Hasher
h0 = IO (Digest len) -> Digest len
forall a. IO a -> a
unsafeDupablePerformIO (IO (Digest len) -> Digest len) -> IO (Digest len) -> Digest len
forall a b. (a -> b) -> a -> b
$ do
  Hasher
h1 <- Hasher -> IO Hasher
BIO.copyHasher Hasher
h0
  Hasher
-> (Ptr HasherInternal -> IO (Digest len)) -> IO (Digest len)
forall a. Hasher -> (Ptr HasherInternal -> IO a) -> IO a
BIO.withHasherInternal Hasher
h1 ((Ptr HasherInternal -> IO (Digest len)) -> IO (Digest len))
-> (Ptr HasherInternal -> IO (Digest len)) -> IO (Digest len)
forall a b. (a -> b) -> a -> b
$ \ph1 :: Ptr HasherInternal
ph1 ->
    Ptr HasherInternal -> IO (Digest len)
forall (len :: Nat).
KnownNat len =>
Ptr HasherInternal -> IO (Digest len)
BIO.finalize Ptr HasherInternal
ph1
{-# NOINLINE finalize #-}