{-# LANGUAGE TypeFamilies #-}
module Crypto.Noise.Hash.BLAKE2s
(
BLAKE2s
) where
import qualified Crypto.Hash as H
import qualified Crypto.MAC.HMAC as M
import Data.ByteArray (ScrubbedBytes, convert, empty, snoc)
import Data.List (unfoldr)
import Data.Word (Word8)
import Crypto.Noise.Hash
data BLAKE2s
instance Hash BLAKE2s where
newtype ChainingKey BLAKE2s = HCKB2s ScrubbedBytes
newtype Digest BLAKE2s = HDB2s (H.Digest H.Blake2s_256)
hashName :: forall (proxy :: * -> *). proxy BLAKE2s -> ScrubbedBytes
hashName proxy BLAKE2s
_ = ScrubbedBytes
"BLAKE2s"
hashLength :: forall (proxy :: * -> *). proxy BLAKE2s -> Int
hashLength proxy BLAKE2s
_ = Int
32
hash :: ScrubbedBytes -> Digest BLAKE2s
hash = ScrubbedBytes -> Digest BLAKE2s
hash'
hashHKDF :: ChainingKey BLAKE2s -> ScrubbedBytes -> Word8 -> [ScrubbedBytes]
hashHKDF = ChainingKey BLAKE2s -> ScrubbedBytes -> Word8 -> [ScrubbedBytes]
hkdf
hashBytesToCK :: ScrubbedBytes -> ChainingKey BLAKE2s
hashBytesToCK = ScrubbedBytes -> ChainingKey BLAKE2s
bytesToCK
hashCKToBytes :: ChainingKey BLAKE2s -> ScrubbedBytes
hashCKToBytes = ChainingKey BLAKE2s -> ScrubbedBytes
ckToBytes
hashToBytes :: Digest BLAKE2s -> ScrubbedBytes
hashToBytes = Digest BLAKE2s -> ScrubbedBytes
toBytes
hash' :: ScrubbedBytes
-> Digest BLAKE2s
hash' :: ScrubbedBytes -> Digest BLAKE2s
hash' ScrubbedBytes
bs = Digest Blake2s_256 -> Digest BLAKE2s
HDB2s (Digest Blake2s_256 -> Digest BLAKE2s)
-> Digest Blake2s_256 -> Digest BLAKE2s
forall a b. (a -> b) -> a -> b
$ ScrubbedBytes -> Digest Blake2s_256
forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
ba -> Digest a
H.hash ScrubbedBytes
bs
hkdf :: ChainingKey BLAKE2s
-> ScrubbedBytes
-> Word8
-> [ScrubbedBytes]
hkdf :: ChainingKey BLAKE2s -> ScrubbedBytes -> Word8 -> [ScrubbedBytes]
hkdf (HCKB2s ScrubbedBytes
ck) ScrubbedBytes
keyMat Word8
numOutputs = (ScrubbedBytes, Word8) -> [ScrubbedBytes]
loop (ScrubbedBytes
forall a. ByteArray a => a
empty, Word8
1)
where
hmac :: key -> message -> ScrubbedBytes
hmac key
key message
info = HMAC Blake2s_256 -> ScrubbedBytes
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert (key -> message -> HMAC Blake2s_256
forall key message a.
(ByteArrayAccess key, ByteArrayAccess message, HashAlgorithm a) =>
key -> message -> HMAC a
M.hmac key
key message
info :: M.HMAC H.Blake2s_256) :: ScrubbedBytes
tempKey :: ScrubbedBytes
tempKey = ScrubbedBytes -> ScrubbedBytes -> ScrubbedBytes
forall {key} {message}.
(ByteArrayAccess key, ByteArrayAccess message) =>
key -> message -> ScrubbedBytes
hmac ScrubbedBytes
ck ScrubbedBytes
keyMat
loop :: (ScrubbedBytes, Word8) -> [ScrubbedBytes]
loop = ((ScrubbedBytes, Word8)
-> Maybe (ScrubbedBytes, (ScrubbedBytes, Word8)))
-> (ScrubbedBytes, Word8) -> [ScrubbedBytes]
forall b a. (b -> Maybe (a, b)) -> b -> [a]
unfoldr (((ScrubbedBytes, Word8)
-> Maybe (ScrubbedBytes, (ScrubbedBytes, Word8)))
-> (ScrubbedBytes, Word8) -> [ScrubbedBytes])
-> ((ScrubbedBytes, Word8)
-> Maybe (ScrubbedBytes, (ScrubbedBytes, Word8)))
-> (ScrubbedBytes, Word8)
-> [ScrubbedBytes]
forall a b. (a -> b) -> a -> b
$ \(ScrubbedBytes
c, Word8
i) -> let r :: ScrubbedBytes
r = ScrubbedBytes -> ScrubbedBytes -> ScrubbedBytes
forall {key} {message}.
(ByteArrayAccess key, ByteArrayAccess message) =>
key -> message -> ScrubbedBytes
hmac ScrubbedBytes
tempKey (ScrubbedBytes
c ScrubbedBytes -> Word8 -> ScrubbedBytes
forall a. ByteArray a => a -> Word8 -> a
`snoc` Word8
i) in
if Word8
i Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0
then Maybe (ScrubbedBytes, (ScrubbedBytes, Word8))
forall a. Maybe a
Nothing
else if Word8
i Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
numOutputs
then (ScrubbedBytes, (ScrubbedBytes, Word8))
-> Maybe (ScrubbedBytes, (ScrubbedBytes, Word8))
forall a. a -> Maybe a
Just (ScrubbedBytes
r, (ScrubbedBytes
r, Word8
i Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
1))
else Maybe (ScrubbedBytes, (ScrubbedBytes, Word8))
forall a. Maybe a
Nothing
bytesToCK :: ScrubbedBytes
-> ChainingKey BLAKE2s
bytesToCK :: ScrubbedBytes -> ChainingKey BLAKE2s
bytesToCK = ScrubbedBytes -> ChainingKey BLAKE2s
HCKB2s
ckToBytes :: ChainingKey BLAKE2s
-> ScrubbedBytes
ckToBytes :: ChainingKey BLAKE2s -> ScrubbedBytes
ckToBytes (HCKB2s ScrubbedBytes
ck) = ScrubbedBytes
ck
toBytes :: Digest BLAKE2s
-> ScrubbedBytes
toBytes :: Digest BLAKE2s -> ScrubbedBytes
toBytes (HDB2s Digest Blake2s_256
d) = Digest Blake2s_256 -> ScrubbedBytes
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert Digest Blake2s_256
d