{-# LANGUAGE ViewPatterns, LambdaCase #-}
module Crypto.Sha256.Hmac.Implementation where
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Function(on)
import Data.Word
import Crypto.Sha256 as Sha256
import Crypto.Sha256.Subtle
type HmacKeyPlain = ByteString
nullBuffer :: ByteString
nullBuffer :: ByteString
nullBuffer = Int -> Word8 -> ByteString
BS.replicate Int
64 Word8
0
data HmacKey
= HmacKey_Plain {-# UNPACK #-} !HmacKeyPlain HmacKeyHashed
| HmacKey_Hashed {-# UNPACK #-} !HmacKeyHashed
instance Eq HmacKey where
(HmacKey_Plain ByteString
a HmacKeyHashed
_) == :: HmacKey -> HmacKey -> Bool
== (HmacKey_Plain ByteString
b HmacKeyHashed
_) = ByteString -> ByteString -> Bool
hmacKeyPlain_eq ByteString
a ByteString
b
HmacKey
a == HmacKey
b = HmacKey -> HmacKeyHashed
hmacKey_toHashed HmacKey
a HmacKeyHashed -> HmacKeyHashed -> Bool
forall a. Eq a => a -> a -> Bool
== HmacKey -> HmacKeyHashed
hmacKey_toHashed HmacKey
b
instance Ord HmacKey where
compare :: HmacKey -> HmacKey -> Ordering
compare = HmacKeyHashed -> HmacKeyHashed -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (HmacKeyHashed -> HmacKeyHashed -> Ordering)
-> (HmacKey -> HmacKeyHashed) -> HmacKey -> HmacKey -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` HmacKey -> HmacKeyHashed
hmacKey_toHashed
hmacKeyPlain_eq :: HmacKeyPlain -> HmacKeyPlain -> Bool
hmacKeyPlain_eq :: ByteString -> ByteString -> Bool
hmacKeyPlain_eq ByteString
a ByteString
b =
case (ByteString -> Int
BS.length ByteString
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
64, ByteString -> Int
BS.length ByteString
b Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
64) of
(Bool
False, Bool
False) -> (ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(==) (ByteString -> ByteString -> Bool)
-> (ByteString -> ByteString) -> ByteString -> ByteString -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` ByteString -> ByteString
normalize) ByteString
a ByteString
b
(Bool
True, Bool
False) -> ByteString -> ByteString -> Bool
checkEq ByteString
a ByteString
b
(Bool
False, Bool
True) -> ByteString -> ByteString -> Bool
checkEq ByteString
b ByteString
a
(Bool
True, Bool
True) -> ByteString
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
b
where
normalize :: ByteString -> ByteString
normalize = (Word8 -> Bool) -> ByteString -> ByteString
BS.dropWhileEnd (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
0)
checkEq :: ByteString -> ByteString -> Bool
checkEq ByteString
x (ByteString -> ByteString
normalize -> ByteString
y)
| ByteString -> Int
BS.length ByteString
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
32 Bool -> Bool -> Bool
|| ByteString -> Int
BS.length ByteString
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
16 = Bool
False
| Bool
otherwise = ByteString -> ByteString
normalize (ByteString -> ByteString
Sha256.hash ByteString
x) ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
y
hmacKey_ipad :: HmacKey -> Sha256State
hmacKey_ipad :: HmacKey -> Sha256State
hmacKey_ipad = HmacKeyHashed -> Sha256State
hmacKeyHashed_ipad (HmacKeyHashed -> Sha256State)
-> (HmacKey -> HmacKeyHashed) -> HmacKey -> Sha256State
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HmacKey -> HmacKeyHashed
hmacKey_toHashed
hmacKey_runIpadCtx :: HmacKey -> ByteString -> Sha256Ctx
hmacKey_runIpadCtx :: HmacKey -> ByteString -> Sha256Ctx
hmacKey_runIpadCtx HmacKey
k ByteString
b = Word64 -> ByteString -> Sha256State -> Sha256Ctx
sha256state_runWith Word64
1 ByteString
b (HmacKey -> Sha256State
hmacKey_ipad HmacKey
k)
hmacKey_ipadCtx :: HmacKey -> Sha256Ctx
hmacKey_ipadCtx :: HmacKey -> Sha256Ctx
hmacKey_ipadCtx = (HmacKey -> ByteString -> Sha256Ctx)
-> ByteString -> HmacKey -> Sha256Ctx
forall a b c. (a -> b -> c) -> b -> a -> c
flip HmacKey -> ByteString -> Sha256Ctx
hmacKey_runIpadCtx ByteString
BS.empty
hmacKey_opad :: HmacKey -> Sha256State
hmacKey_opad :: HmacKey -> Sha256State
hmacKey_opad = HmacKeyHashed -> Sha256State
hmacKeyHashed_opad (HmacKeyHashed -> Sha256State)
-> (HmacKey -> HmacKeyHashed) -> HmacKey -> Sha256State
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HmacKey -> HmacKeyHashed
hmacKey_toHashed
hmacKey_runOpadCtx :: HmacKey -> ByteString -> Sha256Ctx
hmacKey_runOpadCtx :: HmacKey -> ByteString -> Sha256Ctx
hmacKey_runOpadCtx HmacKey
k ByteString
b = Word64 -> ByteString -> Sha256State -> Sha256Ctx
sha256state_runWith Word64
1 ByteString
b (HmacKey -> Sha256State
hmacKey_opad HmacKey
k)
hmacKey_opadCtx :: HmacKey -> Sha256Ctx
hmacKey_opadCtx :: HmacKey -> Sha256Ctx
hmacKey_opadCtx = (HmacKey -> ByteString -> Sha256Ctx)
-> ByteString -> HmacKey -> Sha256Ctx
forall a b c. (a -> b -> c) -> b -> a -> c
flip HmacKey -> ByteString -> Sha256Ctx
hmacKey_runOpadCtx ByteString
BS.empty
hmacKey_toHashed :: HmacKey -> HmacKeyHashed
hmacKey_toHashed :: HmacKey -> HmacKeyHashed
hmacKey_toHashed = \case
HmacKey_Plain ByteString
_ HmacKeyHashed
x -> HmacKeyHashed
x
HmacKey_Hashed HmacKeyHashed
x -> HmacKeyHashed
x
data HmacKeyLike
= HmacKeyLike_Plain {-# UNPACK #-} !HmacKeyPlain HmacKeyHashed
| HmacKeyLike_Hashed {-# UNPACK #-} !HmacKeyHashed
| HmacKeyLike_Prefixed {-# UNPACK #-} !HmacKeyPrefixed
hmacKeyPrefixed_eqHashed :: HmacKeyPrefixed -> HmacKeyHashed -> Bool
hmacKeyPrefixed_eqHashed :: HmacKeyPrefixed -> HmacKeyHashed -> Bool
hmacKeyPrefixed_eqHashed HmacKeyPrefixed
a
| HmacKeyPrefixed -> Word64
hmacKeyPrefixed_blockCount HmacKeyPrefixed
a Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word64
1 = Bool -> HmacKeyHashed -> Bool
forall a b. a -> b -> a
const Bool
False
| Bool
otherwise = \HmacKeyHashed
b -> HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_ipadCtx HmacKeyPrefixed
a Sha256Ctx -> Sha256Ctx -> Bool
forall a. Eq a => a -> a -> Bool
== HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_ipadCtx HmacKeyHashed
b
Bool -> Bool -> Bool
&& HmacKeyPrefixed -> Sha256State
hmacKeyPrefixed_opad HmacKeyPrefixed
a Sha256State -> Sha256State -> Bool
forall a. Eq a => a -> a -> Bool
== HmacKeyHashed -> Sha256State
hmacKeyHashed_opad HmacKeyHashed
b
instance Eq HmacKeyLike where
(HmacKeyLike_Plain ByteString
a HmacKeyHashed
_) == :: HmacKeyLike -> HmacKeyLike -> Bool
== (HmacKeyLike_Plain ByteString
b HmacKeyHashed
_) = ByteString -> ByteString -> Bool
hmacKeyPlain_eq ByteString
a ByteString
b
(HmacKeyLike_Plain ByteString
_ HmacKeyHashed
a) == (HmacKeyLike_Hashed HmacKeyHashed
b) = HmacKeyHashed
a HmacKeyHashed -> HmacKeyHashed -> Bool
forall a. Eq a => a -> a -> Bool
== HmacKeyHashed
b
(HmacKeyLike_Plain ByteString
_ HmacKeyHashed
a) == (HmacKeyLike_Prefixed HmacKeyPrefixed
b) = HmacKeyPrefixed -> HmacKeyHashed -> Bool
hmacKeyPrefixed_eqHashed HmacKeyPrefixed
b HmacKeyHashed
a
(HmacKeyLike_Hashed HmacKeyHashed
a) == (HmacKeyLike_Plain ByteString
_ HmacKeyHashed
b) = HmacKeyHashed
a HmacKeyHashed -> HmacKeyHashed -> Bool
forall a. Eq a => a -> a -> Bool
== HmacKeyHashed
b
(HmacKeyLike_Hashed HmacKeyHashed
a) == (HmacKeyLike_Hashed HmacKeyHashed
b) = HmacKeyHashed
a HmacKeyHashed -> HmacKeyHashed -> Bool
forall a. Eq a => a -> a -> Bool
== HmacKeyHashed
b
(HmacKeyLike_Hashed HmacKeyHashed
a) == (HmacKeyLike_Prefixed HmacKeyPrefixed
b) = HmacKeyPrefixed -> HmacKeyHashed -> Bool
hmacKeyPrefixed_eqHashed HmacKeyPrefixed
b HmacKeyHashed
a
(HmacKeyLike_Prefixed HmacKeyPrefixed
a) == (HmacKeyLike_Plain ByteString
_ HmacKeyHashed
b) = HmacKeyPrefixed -> HmacKeyHashed -> Bool
hmacKeyPrefixed_eqHashed HmacKeyPrefixed
a HmacKeyHashed
b
(HmacKeyLike_Prefixed HmacKeyPrefixed
a) == (HmacKeyLike_Hashed HmacKeyHashed
b) = HmacKeyPrefixed -> HmacKeyHashed -> Bool
hmacKeyPrefixed_eqHashed HmacKeyPrefixed
a HmacKeyHashed
b
(HmacKeyLike_Prefixed HmacKeyPrefixed
a) == (HmacKeyLike_Prefixed HmacKeyPrefixed
b) = HmacKeyPrefixed
a HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
forall a. Eq a => a -> a -> Bool
== HmacKeyPrefixed
b
instance Ord HmacKeyLike where
compare :: HmacKeyLike -> HmacKeyLike -> Ordering
compare = HmacKeyPrefixed -> HmacKeyPrefixed -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (HmacKeyPrefixed -> HmacKeyPrefixed -> Ordering)
-> (HmacKeyLike -> HmacKeyPrefixed)
-> HmacKeyLike
-> HmacKeyLike
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` HmacKeyLike -> HmacKeyPrefixed
hmacKeyLike_toPrefixed
hmacKeyLike_toPrefixed :: HmacKeyLike -> HmacKeyPrefixed
hmacKeyLike_toPrefixed :: HmacKeyLike -> HmacKeyPrefixed
hmacKeyLike_toPrefixed = \case
HmacKeyLike_Plain ByteString
_ HmacKeyHashed
b -> HmacKeyHashed -> HmacKeyPrefixed
hmacKeyPrefixed_initHashed HmacKeyHashed
b
HmacKeyLike_Hashed HmacKeyHashed
b -> HmacKeyHashed -> HmacKeyPrefixed
hmacKeyPrefixed_initHashed HmacKeyHashed
b
HmacKeyLike_Prefixed HmacKeyPrefixed
b -> HmacKeyPrefixed
b
hmacKeyPrefixed_initHashed :: HmacKeyHashed -> HmacKeyPrefixed
hmacKeyPrefixed_initHashed :: HmacKeyHashed -> HmacKeyPrefixed
hmacKeyPrefixed_initHashed HmacKeyHashed
k = Sha256State -> Sha256Ctx -> HmacKeyPrefixed
HmacKeyPrefixed (HmacKeyHashed -> Sha256State
hmacKeyHashed_opad HmacKeyHashed
k) (HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_ipadCtx HmacKeyHashed
k)
hmacKeyLike_ipadCtx :: HmacKeyLike -> Sha256Ctx
hmacKeyLike_ipadCtx :: HmacKeyLike -> Sha256Ctx
hmacKeyLike_ipadCtx = \case
HmacKeyLike_Plain ByteString
_ HmacKeyHashed
x -> HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_ipadCtx HmacKeyHashed
x
HmacKeyLike_Hashed HmacKeyHashed
x -> HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_ipadCtx HmacKeyHashed
x
HmacKeyLike_Prefixed HmacKeyPrefixed
x -> HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_ipadCtx HmacKeyPrefixed
x
hmacKeyLike_opad :: HmacKeyLike -> Sha256State
hmacKeyLike_opad :: HmacKeyLike -> Sha256State
hmacKeyLike_opad = \case
HmacKeyLike_Plain ByteString
_ HmacKeyHashed
x -> HmacKeyHashed -> Sha256State
hmacKeyHashed_opad HmacKeyHashed
x
HmacKeyLike_Hashed HmacKeyHashed
x -> HmacKeyHashed -> Sha256State
hmacKeyHashed_opad HmacKeyHashed
x
HmacKeyLike_Prefixed HmacKeyPrefixed
x -> HmacKeyPrefixed -> Sha256State
hmacKeyPrefixed_opad HmacKeyPrefixed
x
hmacKeyLike_opadCtx :: HmacKeyLike -> Sha256Ctx
hmacKeyLike_opadCtx :: HmacKeyLike -> Sha256Ctx
hmacKeyLike_opadCtx = \case
HmacKeyLike_Plain ByteString
_ HmacKeyHashed
x -> HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_opadCtx HmacKeyHashed
x
HmacKeyLike_Hashed HmacKeyHashed
x -> HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_opadCtx HmacKeyHashed
x
HmacKeyLike_Prefixed HmacKeyPrefixed
x -> HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_opadCtx HmacKeyPrefixed
x
hmacKeyLike_runIpadCtx :: HmacKeyLike -> ByteString -> Sha256Ctx
hmacKeyLike_runIpadCtx :: HmacKeyLike -> ByteString -> Sha256Ctx
hmacKeyLike_runIpadCtx = \case
HmacKeyLike_Plain ByteString
_ HmacKeyHashed
x -> HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runIpadCtx HmacKeyHashed
x
HmacKeyLike_Hashed HmacKeyHashed
x -> HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runIpadCtx HmacKeyHashed
x
HmacKeyLike_Prefixed HmacKeyPrefixed
x -> HmacKeyPrefixed -> ByteString -> Sha256Ctx
hmacKeyPrefixed_runIpadCtx HmacKeyPrefixed
x
hmacKeyLike_runOpadCtx :: HmacKeyLike -> ByteString -> Sha256Ctx
hmacKeyLike_runOpadCtx :: HmacKeyLike -> ByteString -> Sha256Ctx
hmacKeyLike_runOpadCtx = \case
HmacKeyLike_Plain ByteString
_ HmacKeyHashed
x -> HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runOpadCtx HmacKeyHashed
x
HmacKeyLike_Hashed HmacKeyHashed
x -> HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runOpadCtx HmacKeyHashed
x
HmacKeyLike_Prefixed HmacKeyPrefixed
x -> HmacKeyPrefixed -> ByteString -> Sha256Ctx
hmacKeyPrefixed_runOpadCtx HmacKeyPrefixed
x
data HmacCtx = HmacCtx
{ HmacCtx -> Sha256State
hmacCtx_opad :: {-# UNPACK #-} !Sha256State
, HmacCtx -> Sha256Ctx
hmacCtx_ipadCtx :: {-# UNPACK #-} !Sha256Ctx
} deriving (HmacCtx -> HmacCtx -> Bool
(HmacCtx -> HmacCtx -> Bool)
-> (HmacCtx -> HmacCtx -> Bool) -> Eq HmacCtx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HmacCtx -> HmacCtx -> Bool
== :: HmacCtx -> HmacCtx -> Bool
$c/= :: HmacCtx -> HmacCtx -> Bool
/= :: HmacCtx -> HmacCtx -> Bool
Eq, Eq HmacCtx
Eq HmacCtx =>
(HmacCtx -> HmacCtx -> Ordering)
-> (HmacCtx -> HmacCtx -> Bool)
-> (HmacCtx -> HmacCtx -> Bool)
-> (HmacCtx -> HmacCtx -> Bool)
-> (HmacCtx -> HmacCtx -> Bool)
-> (HmacCtx -> HmacCtx -> HmacCtx)
-> (HmacCtx -> HmacCtx -> HmacCtx)
-> Ord HmacCtx
HmacCtx -> HmacCtx -> Bool
HmacCtx -> HmacCtx -> Ordering
HmacCtx -> HmacCtx -> HmacCtx
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: HmacCtx -> HmacCtx -> Ordering
compare :: HmacCtx -> HmacCtx -> Ordering
$c< :: HmacCtx -> HmacCtx -> Bool
< :: HmacCtx -> HmacCtx -> Bool
$c<= :: HmacCtx -> HmacCtx -> Bool
<= :: HmacCtx -> HmacCtx -> Bool
$c> :: HmacCtx -> HmacCtx -> Bool
> :: HmacCtx -> HmacCtx -> Bool
$c>= :: HmacCtx -> HmacCtx -> Bool
>= :: HmacCtx -> HmacCtx -> Bool
$cmax :: HmacCtx -> HmacCtx -> HmacCtx
max :: HmacCtx -> HmacCtx -> HmacCtx
$cmin :: HmacCtx -> HmacCtx -> HmacCtx
min :: HmacCtx -> HmacCtx -> HmacCtx
Ord)
data HmacKeyHashed = HmacKeyHashed
{ HmacKeyHashed -> Sha256State
hmacKeyHashed_opad :: {-# UNPACK #-} !Sha256State
, HmacKeyHashed -> Sha256State
hmacKeyHashed_ipad :: {-# UNPACK #-} !Sha256State
} deriving (HmacKeyHashed -> HmacKeyHashed -> Bool
(HmacKeyHashed -> HmacKeyHashed -> Bool)
-> (HmacKeyHashed -> HmacKeyHashed -> Bool) -> Eq HmacKeyHashed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HmacKeyHashed -> HmacKeyHashed -> Bool
== :: HmacKeyHashed -> HmacKeyHashed -> Bool
$c/= :: HmacKeyHashed -> HmacKeyHashed -> Bool
/= :: HmacKeyHashed -> HmacKeyHashed -> Bool
Eq, Eq HmacKeyHashed
Eq HmacKeyHashed =>
(HmacKeyHashed -> HmacKeyHashed -> Ordering)
-> (HmacKeyHashed -> HmacKeyHashed -> Bool)
-> (HmacKeyHashed -> HmacKeyHashed -> Bool)
-> (HmacKeyHashed -> HmacKeyHashed -> Bool)
-> (HmacKeyHashed -> HmacKeyHashed -> Bool)
-> (HmacKeyHashed -> HmacKeyHashed -> HmacKeyHashed)
-> (HmacKeyHashed -> HmacKeyHashed -> HmacKeyHashed)
-> Ord HmacKeyHashed
HmacKeyHashed -> HmacKeyHashed -> Bool
HmacKeyHashed -> HmacKeyHashed -> Ordering
HmacKeyHashed -> HmacKeyHashed -> HmacKeyHashed
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: HmacKeyHashed -> HmacKeyHashed -> Ordering
compare :: HmacKeyHashed -> HmacKeyHashed -> Ordering
$c< :: HmacKeyHashed -> HmacKeyHashed -> Bool
< :: HmacKeyHashed -> HmacKeyHashed -> Bool
$c<= :: HmacKeyHashed -> HmacKeyHashed -> Bool
<= :: HmacKeyHashed -> HmacKeyHashed -> Bool
$c> :: HmacKeyHashed -> HmacKeyHashed -> Bool
> :: HmacKeyHashed -> HmacKeyHashed -> Bool
$c>= :: HmacKeyHashed -> HmacKeyHashed -> Bool
>= :: HmacKeyHashed -> HmacKeyHashed -> Bool
$cmax :: HmacKeyHashed -> HmacKeyHashed -> HmacKeyHashed
max :: HmacKeyHashed -> HmacKeyHashed -> HmacKeyHashed
$cmin :: HmacKeyHashed -> HmacKeyHashed -> HmacKeyHashed
min :: HmacKeyHashed -> HmacKeyHashed -> HmacKeyHashed
Ord)
hmacKeyHashed_ipadCtx :: HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_ipadCtx :: HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_ipadCtx = (HmacKeyHashed -> ByteString -> Sha256Ctx)
-> ByteString -> HmacKeyHashed -> Sha256Ctx
forall a b c. (a -> b -> c) -> b -> a -> c
flip HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runIpadCtx ByteString
BS.empty
hmacKeyHashed_runIpadCtx :: HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runIpadCtx :: HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runIpadCtx HmacKeyHashed
k ByteString
b = Word64 -> ByteString -> Sha256State -> Sha256Ctx
sha256state_runWith Word64
1 ByteString
b (HmacKeyHashed -> Sha256State
hmacKeyHashed_ipad HmacKeyHashed
k)
hmacKeyHashed_opadCtx :: HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_opadCtx :: HmacKeyHashed -> Sha256Ctx
hmacKeyHashed_opadCtx = (HmacKeyHashed -> ByteString -> Sha256Ctx)
-> ByteString -> HmacKeyHashed -> Sha256Ctx
forall a b c. (a -> b -> c) -> b -> a -> c
flip HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runOpadCtx ByteString
BS.empty
hmacKeyHashed_runOpadCtx :: HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runOpadCtx :: HmacKeyHashed -> ByteString -> Sha256Ctx
hmacKeyHashed_runOpadCtx HmacKeyHashed
k ByteString
b = Word64 -> ByteString -> Sha256State -> Sha256Ctx
sha256state_runWith Word64
1 ByteString
b (HmacKeyHashed -> Sha256State
hmacKeyHashed_opad HmacKeyHashed
k)
data HmacKeyPrefixed = HmacKeyPrefixed
{ HmacKeyPrefixed -> Sha256State
hmacKeyPrefixed_opad :: {-# UNPACK #-} !Sha256State
, HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_ipadCtx :: {-# UNPACK #-} !Sha256Ctx
} deriving (HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
(HmacKeyPrefixed -> HmacKeyPrefixed -> Bool)
-> (HmacKeyPrefixed -> HmacKeyPrefixed -> Bool)
-> Eq HmacKeyPrefixed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
== :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
$c/= :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
/= :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
Eq, Eq HmacKeyPrefixed
Eq HmacKeyPrefixed =>
(HmacKeyPrefixed -> HmacKeyPrefixed -> Ordering)
-> (HmacKeyPrefixed -> HmacKeyPrefixed -> Bool)
-> (HmacKeyPrefixed -> HmacKeyPrefixed -> Bool)
-> (HmacKeyPrefixed -> HmacKeyPrefixed -> Bool)
-> (HmacKeyPrefixed -> HmacKeyPrefixed -> Bool)
-> (HmacKeyPrefixed -> HmacKeyPrefixed -> HmacKeyPrefixed)
-> (HmacKeyPrefixed -> HmacKeyPrefixed -> HmacKeyPrefixed)
-> Ord HmacKeyPrefixed
HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
HmacKeyPrefixed -> HmacKeyPrefixed -> Ordering
HmacKeyPrefixed -> HmacKeyPrefixed -> HmacKeyPrefixed
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: HmacKeyPrefixed -> HmacKeyPrefixed -> Ordering
compare :: HmacKeyPrefixed -> HmacKeyPrefixed -> Ordering
$c< :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
< :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
$c<= :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
<= :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
$c> :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
> :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
$c>= :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
>= :: HmacKeyPrefixed -> HmacKeyPrefixed -> Bool
$cmax :: HmacKeyPrefixed -> HmacKeyPrefixed -> HmacKeyPrefixed
max :: HmacKeyPrefixed -> HmacKeyPrefixed -> HmacKeyPrefixed
$cmin :: HmacKeyPrefixed -> HmacKeyPrefixed -> HmacKeyPrefixed
min :: HmacKeyPrefixed -> HmacKeyPrefixed -> HmacKeyPrefixed
Ord)
hmacKeyPrefixed_runIpadCtx :: HmacKeyPrefixed -> ByteString -> Sha256Ctx
hmacKeyPrefixed_runIpadCtx :: HmacKeyPrefixed -> ByteString -> Sha256Ctx
hmacKeyPrefixed_runIpadCtx HmacKeyPrefixed
k ByteString
b = ByteString -> Sha256Ctx -> Sha256Ctx
sha256_feed ByteString
b (HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_ipadCtx HmacKeyPrefixed
k)
hmacKeyPrefixed_runOpadCtx :: HmacKeyPrefixed -> ByteString -> Sha256Ctx
hmacKeyPrefixed_runOpadCtx :: HmacKeyPrefixed -> ByteString -> Sha256Ctx
hmacKeyPrefixed_runOpadCtx HmacKeyPrefixed
k ByteString
b = Word64 -> ByteString -> Sha256State -> Sha256Ctx
sha256state_runWith Word64
1 ByteString
b (HmacKeyPrefixed -> Sha256State
hmacKeyPrefixed_opad HmacKeyPrefixed
k)
hmacKeyPrefixed_opadCtx :: HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_opadCtx :: HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_opadCtx = (HmacKeyPrefixed -> ByteString -> Sha256Ctx)
-> ByteString -> HmacKeyPrefixed -> Sha256Ctx
forall a b c. (a -> b -> c) -> b -> a -> c
flip HmacKeyPrefixed -> ByteString -> Sha256Ctx
hmacKeyPrefixed_runOpadCtx ByteString
BS.empty
hmacKeyPrefixed_blockCount :: HmacKeyPrefixed -> Word64
hmacKeyPrefixed_blockCount :: HmacKeyPrefixed -> Word64
hmacKeyPrefixed_blockCount = Sha256Ctx -> Word64
sha256_blockCount (Sha256Ctx -> Word64)
-> (HmacKeyPrefixed -> Sha256Ctx) -> HmacKeyPrefixed -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HmacKeyPrefixed -> Sha256Ctx
hmacKeyPrefixed_ipadCtx