module Crypto.PHKDF.HMAC.Subtle
( HmacCtx(..)
, HmacKey(..)
, hmacKey_ipad
, hmacKey_opad
) where
import qualified Crypto.Hash.SHA256 as SHA256
data HmacCtx = HmacCtx
{ HmacCtx -> Ctx
hmacCtx_ipad :: !SHA256.Ctx
, HmacCtx -> Ctx
hmacCtx_opad :: !SHA256.Ctx
} 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)
newtype HmacKey = HmacKey { HmacKey -> HmacCtx
hmacKey_run :: HmacCtx } deriving (HmacKey -> HmacKey -> Bool
(HmacKey -> HmacKey -> Bool)
-> (HmacKey -> HmacKey -> Bool) -> Eq HmacKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HmacKey -> HmacKey -> Bool
== :: HmacKey -> HmacKey -> Bool
$c/= :: HmacKey -> HmacKey -> Bool
/= :: HmacKey -> HmacKey -> Bool
Eq)
hmacKey_ipad :: HmacKey -> SHA256.Ctx
hmacKey_ipad :: HmacKey -> Ctx
hmacKey_ipad (HmacKey HmacCtx
ctx) = HmacCtx -> Ctx
hmacCtx_ipad HmacCtx
ctx
hmacKey_opad :: HmacKey -> SHA256.Ctx
hmacKey_opad :: HmacKey -> Ctx
hmacKey_opad (HmacKey HmacCtx
ctx) = HmacCtx -> Ctx
hmacCtx_opad HmacCtx
ctx