{-# LANGUAGE OverloadedStrings #-}
module Crypto.PHKDF where
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.Function((&))
import Data.Word
import Data.Stream (Stream)
import Data.Vector (Vector)
import qualified Data.Vector as V
import Network.ByteOrder (word32)
import Crypto.Encoding.PHKDF
import Crypto.Encoding.SHA3.TupleHash
import Crypto.PHKDF.Primitives
import Crypto.PHKDF.Primitives.Assert
data PhkdfInputBlock = PhkdfInputBlock
{ PhkdfInputBlock -> ByteString
phkdfInputBlock_seguid :: !ByteString
, PhkdfInputBlock -> ByteString
phkdfInputBlock_domainTag :: !ByteString
, PhkdfInputBlock -> ByteString
phkdfInputBlock_longTag :: !ByteString
, PhkdfInputBlock -> Vector ByteString
phkdfInputBlock_tags :: !(Vector ByteString)
, PhkdfInputBlock -> Word32
phkdfInputBlock_rounds :: !Word32
} deriving (PhkdfInputBlock -> PhkdfInputBlock -> Bool
(PhkdfInputBlock -> PhkdfInputBlock -> Bool)
-> (PhkdfInputBlock -> PhkdfInputBlock -> Bool)
-> Eq PhkdfInputBlock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
== :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
$c/= :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
/= :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
Eq, Eq PhkdfInputBlock
Eq PhkdfInputBlock =>
(PhkdfInputBlock -> PhkdfInputBlock -> Ordering)
-> (PhkdfInputBlock -> PhkdfInputBlock -> Bool)
-> (PhkdfInputBlock -> PhkdfInputBlock -> Bool)
-> (PhkdfInputBlock -> PhkdfInputBlock -> Bool)
-> (PhkdfInputBlock -> PhkdfInputBlock -> Bool)
-> (PhkdfInputBlock -> PhkdfInputBlock -> PhkdfInputBlock)
-> (PhkdfInputBlock -> PhkdfInputBlock -> PhkdfInputBlock)
-> Ord PhkdfInputBlock
PhkdfInputBlock -> PhkdfInputBlock -> Bool
PhkdfInputBlock -> PhkdfInputBlock -> Ordering
PhkdfInputBlock -> PhkdfInputBlock -> PhkdfInputBlock
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 :: PhkdfInputBlock -> PhkdfInputBlock -> Ordering
compare :: PhkdfInputBlock -> PhkdfInputBlock -> Ordering
$c< :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
< :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
$c<= :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
<= :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
$c> :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
> :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
$c>= :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
>= :: PhkdfInputBlock -> PhkdfInputBlock -> Bool
$cmax :: PhkdfInputBlock -> PhkdfInputBlock -> PhkdfInputBlock
max :: PhkdfInputBlock -> PhkdfInputBlock -> PhkdfInputBlock
$cmin :: PhkdfInputBlock -> PhkdfInputBlock -> PhkdfInputBlock
min :: PhkdfInputBlock -> PhkdfInputBlock -> PhkdfInputBlock
Ord, Int -> PhkdfInputBlock -> ShowS
[PhkdfInputBlock] -> ShowS
PhkdfInputBlock -> String
(Int -> PhkdfInputBlock -> ShowS)
-> (PhkdfInputBlock -> String)
-> ([PhkdfInputBlock] -> ShowS)
-> Show PhkdfInputBlock
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PhkdfInputBlock -> ShowS
showsPrec :: Int -> PhkdfInputBlock -> ShowS
$cshow :: PhkdfInputBlock -> String
show :: PhkdfInputBlock -> String
$cshowList :: [PhkdfInputBlock] -> ShowS
showList :: [PhkdfInputBlock] -> ShowS
Show)
data PhkdfInputArgs = PhkdfInputArgs
{ PhkdfInputArgs -> ByteString
phkdfInputArgs_username :: !ByteString
, PhkdfInputArgs -> ByteString
phkdfInputArgs_password :: !ByteString
, PhkdfInputArgs -> Vector ByteString
phkdfInputArgs_credentials :: !(Vector ByteString)
} deriving (PhkdfInputArgs -> PhkdfInputArgs -> Bool
(PhkdfInputArgs -> PhkdfInputArgs -> Bool)
-> (PhkdfInputArgs -> PhkdfInputArgs -> Bool) -> Eq PhkdfInputArgs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
== :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
$c/= :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
/= :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
Eq, Eq PhkdfInputArgs
Eq PhkdfInputArgs =>
(PhkdfInputArgs -> PhkdfInputArgs -> Ordering)
-> (PhkdfInputArgs -> PhkdfInputArgs -> Bool)
-> (PhkdfInputArgs -> PhkdfInputArgs -> Bool)
-> (PhkdfInputArgs -> PhkdfInputArgs -> Bool)
-> (PhkdfInputArgs -> PhkdfInputArgs -> Bool)
-> (PhkdfInputArgs -> PhkdfInputArgs -> PhkdfInputArgs)
-> (PhkdfInputArgs -> PhkdfInputArgs -> PhkdfInputArgs)
-> Ord PhkdfInputArgs
PhkdfInputArgs -> PhkdfInputArgs -> Bool
PhkdfInputArgs -> PhkdfInputArgs -> Ordering
PhkdfInputArgs -> PhkdfInputArgs -> PhkdfInputArgs
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 :: PhkdfInputArgs -> PhkdfInputArgs -> Ordering
compare :: PhkdfInputArgs -> PhkdfInputArgs -> Ordering
$c< :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
< :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
$c<= :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
<= :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
$c> :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
> :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
$c>= :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
>= :: PhkdfInputArgs -> PhkdfInputArgs -> Bool
$cmax :: PhkdfInputArgs -> PhkdfInputArgs -> PhkdfInputArgs
max :: PhkdfInputArgs -> PhkdfInputArgs -> PhkdfInputArgs
$cmin :: PhkdfInputArgs -> PhkdfInputArgs -> PhkdfInputArgs
min :: PhkdfInputArgs -> PhkdfInputArgs -> PhkdfInputArgs
Ord, Int -> PhkdfInputArgs -> ShowS
[PhkdfInputArgs] -> ShowS
PhkdfInputArgs -> String
(Int -> PhkdfInputArgs -> ShowS)
-> (PhkdfInputArgs -> String)
-> ([PhkdfInputArgs] -> ShowS)
-> Show PhkdfInputArgs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PhkdfInputArgs -> ShowS
showsPrec :: Int -> PhkdfInputArgs -> ShowS
$cshow :: PhkdfInputArgs -> String
show :: PhkdfInputArgs -> String
$cshowList :: [PhkdfInputArgs] -> ShowS
showList :: [PhkdfInputArgs] -> ShowS
Show)
data PhkdfInputTweak = PhkdfInputTweak
{ PhkdfInputTweak -> Vector ByteString
phkdfInputTweak_role :: !(Vector ByteString)
, PhkdfInputTweak -> ByteString
phkdfInputTweak_echoTag :: !ByteString
} deriving (PhkdfInputTweak -> PhkdfInputTweak -> Bool
(PhkdfInputTweak -> PhkdfInputTweak -> Bool)
-> (PhkdfInputTweak -> PhkdfInputTweak -> Bool)
-> Eq PhkdfInputTweak
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
== :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
$c/= :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
/= :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
Eq, Eq PhkdfInputTweak
Eq PhkdfInputTweak =>
(PhkdfInputTweak -> PhkdfInputTweak -> Ordering)
-> (PhkdfInputTweak -> PhkdfInputTweak -> Bool)
-> (PhkdfInputTweak -> PhkdfInputTweak -> Bool)
-> (PhkdfInputTweak -> PhkdfInputTweak -> Bool)
-> (PhkdfInputTweak -> PhkdfInputTweak -> Bool)
-> (PhkdfInputTweak -> PhkdfInputTweak -> PhkdfInputTweak)
-> (PhkdfInputTweak -> PhkdfInputTweak -> PhkdfInputTweak)
-> Ord PhkdfInputTweak
PhkdfInputTweak -> PhkdfInputTweak -> Bool
PhkdfInputTweak -> PhkdfInputTweak -> Ordering
PhkdfInputTweak -> PhkdfInputTweak -> PhkdfInputTweak
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 :: PhkdfInputTweak -> PhkdfInputTweak -> Ordering
compare :: PhkdfInputTweak -> PhkdfInputTweak -> Ordering
$c< :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
< :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
$c<= :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
<= :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
$c> :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
> :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
$c>= :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
>= :: PhkdfInputTweak -> PhkdfInputTweak -> Bool
$cmax :: PhkdfInputTweak -> PhkdfInputTweak -> PhkdfInputTweak
max :: PhkdfInputTweak -> PhkdfInputTweak -> PhkdfInputTweak
$cmin :: PhkdfInputTweak -> PhkdfInputTweak -> PhkdfInputTweak
min :: PhkdfInputTweak -> PhkdfInputTweak -> PhkdfInputTweak
Ord, Int -> PhkdfInputTweak -> ShowS
[PhkdfInputTweak] -> ShowS
PhkdfInputTweak -> String
(Int -> PhkdfInputTweak -> ShowS)
-> (PhkdfInputTweak -> String)
-> ([PhkdfInputTweak] -> ShowS)
-> Show PhkdfInputTweak
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PhkdfInputTweak -> ShowS
showsPrec :: Int -> PhkdfInputTweak -> ShowS
$cshow :: PhkdfInputTweak -> String
show :: PhkdfInputTweak -> String
$cshowList :: [PhkdfInputTweak] -> ShowS
showList :: [PhkdfInputTweak] -> ShowS
Show)
data PhkdfSeed = PhkdfSeed
{ PhkdfSeed -> ByteString
phkdfSeed_seguid :: !ByteString
, PhkdfSeed -> HmacKey
phkdfSeed_seguidKey :: !HmacKey
, PhkdfSeed -> ByteString
phkdfSeed_domainTag :: !ByteString
, PhkdfSeed -> ByteString
phkdfSeed_secret :: !ByteString
} deriving (PhkdfSeed -> PhkdfSeed -> Bool
(PhkdfSeed -> PhkdfSeed -> Bool)
-> (PhkdfSeed -> PhkdfSeed -> Bool) -> Eq PhkdfSeed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhkdfSeed -> PhkdfSeed -> Bool
== :: PhkdfSeed -> PhkdfSeed -> Bool
$c/= :: PhkdfSeed -> PhkdfSeed -> Bool
/= :: PhkdfSeed -> PhkdfSeed -> Bool
Eq)
phkdfSimple :: PhkdfInputBlock -> PhkdfInputArgs -> Stream ByteString
phkdfSimple :: PhkdfInputBlock -> PhkdfInputArgs -> Stream ByteString
phkdfSimple PhkdfInputBlock
block PhkdfInputArgs
args = Stream ByteString
echo
where
domainTag :: ByteString
domainTag = PhkdfInputBlock -> ByteString
phkdfInputBlock_domainTag PhkdfInputBlock
block
seguid :: ByteString
seguid = PhkdfInputBlock -> ByteString
phkdfInputBlock_seguid PhkdfInputBlock
block
longTag :: ByteString
longTag = PhkdfInputBlock -> ByteString
phkdfInputBlock_longTag PhkdfInputBlock
block
tags :: Vector ByteString
tags = PhkdfInputBlock -> Vector ByteString
phkdfInputBlock_tags PhkdfInputBlock
block
rounds :: Word32
rounds = PhkdfInputBlock -> Word32
phkdfInputBlock_rounds PhkdfInputBlock
block
username :: ByteString
username = PhkdfInputArgs -> ByteString
phkdfInputArgs_username PhkdfInputArgs
args
password :: ByteString
password = PhkdfInputArgs -> ByteString
phkdfInputArgs_password PhkdfInputArgs
args
credentials :: Vector ByteString
credentials = PhkdfInputArgs -> Vector ByteString
phkdfInputArgs_credentials PhkdfInputArgs
args
headerExtract :: [ByteString]
headerExtract = [ ByteString
"phkdf-simple0 username", ByteString
username ]
headerUsername :: [ByteString]
headerUsername = [ByteString]
headerExtract [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ [ByteString] -> ByteString -> ByteString -> ByteString
forall (f :: * -> *).
Foldable f =>
f ByteString -> ByteString -> ByteString -> ByteString
usernamePadding [ByteString]
headerExtract ByteString
domainTag ByteString
domainTag ]
headerLongTag :: [ByteString]
headerLongTag =
[ ByteString
longTag
, [ByteString] -> ByteString
B.concat
[ ByteString
"password-hash-key-derivation-function phkdf-simple0\x00"
, Int -> ByteString
forall b. (Integral b, FiniteBits b) => b -> ByteString
leftEncodeFromBytes (ByteString -> Int
B.length ByteString
domainTag)
, Word32 -> ByteString
forall b. (Integral b, FiniteBits b) => b -> ByteString
bareEncode Word32
rounds
]
]
secretKey :: ByteString
secretKey =
ByteString -> PhkdfCtx
phkdfCtx_init ByteString
seguid PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
[ByteString] -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs [ByteString]
headerUsername PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfCtx -> PhkdfCtx
phkdfCtx_assertBufferPosition Word64
32 PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg ByteString
password PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
[ByteString] -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs [ByteString]
headerLongTag PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg ([ByteString]
-> [ByteString]
-> ByteString
-> ByteString
-> ByteString
-> ByteString
forall (f :: * -> *).
Foldable f =>
f ByteString
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> ByteString
passwordPadding [ByteString]
headerUsername [ByteString]
headerLongTag ByteString
longTag ByteString
domainTag ByteString
password) PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfCtx -> PhkdfCtx
phkdfCtx_assertBufferPosition Word64
32 PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs Vector ByteString
credentials PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg (Vector ByteString -> ByteString -> ByteString -> ByteString
forall (f :: * -> *).
Foldable f =>
f ByteString -> ByteString -> ByteString -> ByteString
credentialsPadding Vector ByteString
credentials ByteString
longTag ByteString
domainTag) PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfCtx -> PhkdfCtx
phkdfCtx_assertBufferPosition Word64
29 PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs Vector ByteString
tags PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg (Int -> ByteString
forall b. (Integral b, FiniteBits b) => b -> ByteString
bareEncode (Vector ByteString -> Int
forall a. Vector a -> Int
V.length Vector ByteString
tags)) PhkdfCtx -> (PhkdfCtx -> PhkdfSlowCtx) -> PhkdfSlowCtx
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32
-> ByteString
-> ByteString
-> Word32
-> PhkdfCtx
-> PhkdfSlowCtx
phkdfSlowCtx_extract
(ByteString -> Int -> ByteString
cycleByteStringWithNull ByteString
domainTag)
(ByteString -> Word32
word32 ByteString
"go\x00\x00" Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
2023) ByteString
domainTag
ByteString
"phkdf-simple0 compact" Word32
rounds PhkdfSlowCtx -> (PhkdfSlowCtx -> PhkdfSlowCtx) -> PhkdfSlowCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfSlowCtx -> PhkdfSlowCtx
phkdfSlowCtx_assertBufferPosition Word64
32 PhkdfSlowCtx -> (PhkdfSlowCtx -> PhkdfSlowCtx) -> PhkdfSlowCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx
phkdfSlowCtx_addArgs Vector ByteString
tags PhkdfSlowCtx -> (PhkdfSlowCtx -> ByteString) -> ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString) -> PhkdfSlowCtx -> ByteString
phkdfSlowCtx_finalize (ByteString -> Int -> ByteString
cycleByteStringWithNull ByteString
domainTag)
echoHeader :: ByteString
echoHeader = ByteString -> Int -> ByteString
cycleByteStringWithNull ByteString
"phkdf-simple0 expand echo" Int
30
echo :: Stream ByteString
echo = ByteString -> PhkdfCtx
phkdfCtx_init ByteString
secretKey PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg ByteString
echoHeader PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfCtx -> PhkdfCtx
phkdfCtx_assertBufferPosition Word64
32 PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs Vector ByteString
tags PhkdfCtx -> (PhkdfCtx -> Stream ByteString) -> Stream ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32 -> ByteString -> PhkdfCtx -> Stream ByteString
phkdfCtx_finalizeStream (ByteString -> Int -> ByteString
cycleByteStringWithNull ByteString
domainTag) (ByteString -> Word32
word32 ByteString
"OUT\x00") ByteString
domainTag
phkdfPass :: PhkdfInputBlock -> PhkdfInputArgs -> PhkdfInputTweak -> Stream ByteString
phkdfPass :: PhkdfInputBlock
-> PhkdfInputArgs -> PhkdfInputTweak -> Stream ByteString
phkdfPass PhkdfInputBlock
block PhkdfInputArgs
args = PhkdfInputBlock -> PhkdfInputArgs -> PhkdfSeed
phkdfPass_seedInit PhkdfInputBlock
block PhkdfInputArgs
args PhkdfSeed
-> (PhkdfSeed -> PhkdfInputTweak -> Stream ByteString)
-> PhkdfInputTweak
-> Stream ByteString
forall a b. a -> (a -> b) -> b
& PhkdfSeed -> PhkdfInputTweak -> Stream ByteString
phkdfPass_seedFinalize
phkdfPass_seedInit :: PhkdfInputBlock -> PhkdfInputArgs -> PhkdfSeed
phkdfPass_seedInit :: PhkdfInputBlock -> PhkdfInputArgs -> PhkdfSeed
phkdfPass_seedInit PhkdfInputBlock
block PhkdfInputArgs
args =
PhkdfSeed {
phkdfSeed_seguid :: ByteString
phkdfSeed_seguid = ByteString
seguid,
phkdfSeed_seguidKey :: HmacKey
phkdfSeed_seguidKey = HmacKey
seguidKey,
phkdfSeed_domainTag :: ByteString
phkdfSeed_domainTag = ByteString
domainTag,
phkdfSeed_secret :: ByteString
phkdfSeed_secret = ByteString
secret
}
where
domainTag :: ByteString
domainTag = PhkdfInputBlock -> ByteString
phkdfInputBlock_domainTag PhkdfInputBlock
block
seguid :: ByteString
seguid = PhkdfInputBlock -> ByteString
phkdfInputBlock_seguid PhkdfInputBlock
block
longTag :: ByteString
longTag = PhkdfInputBlock -> ByteString
phkdfInputBlock_longTag PhkdfInputBlock
block
seedTags :: Vector ByteString
seedTags = PhkdfInputBlock -> Vector ByteString
phkdfInputBlock_tags PhkdfInputBlock
block
rounds :: Word32
rounds = PhkdfInputBlock -> Word32
phkdfInputBlock_rounds PhkdfInputBlock
block
username :: ByteString
username = PhkdfInputArgs -> ByteString
phkdfInputArgs_username PhkdfInputArgs
args
password :: ByteString
password = PhkdfInputArgs -> ByteString
phkdfInputArgs_password PhkdfInputArgs
args
credentials :: Vector ByteString
credentials = PhkdfInputArgs -> Vector ByteString
phkdfInputArgs_credentials PhkdfInputArgs
args
headerExtract :: [ByteString]
headerExtract = [ ByteString
"phkdf-pass-v0 username", ByteString
username ]
headerUsername :: [ByteString]
headerUsername = [ByteString]
headerExtract [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ [ByteString] -> ByteString -> ByteString -> ByteString
forall (f :: * -> *).
Foldable f =>
f ByteString -> ByteString -> ByteString -> ByteString
usernamePadding [ByteString]
headerExtract ByteString
domainTag ByteString
domainTag ]
headerLongTag :: [ByteString]
headerLongTag =
[ ByteString
longTag
, [ByteString] -> ByteString
B.concat
[ ByteString
"password hash & key derivation function: phkdf-pass-v0"
, Word32 -> ByteString
forall b. (Integral b, FiniteBits b) => b -> ByteString
bareEncode Word32
rounds
]
]
seguidKey :: HmacKey
seguidKey = ByteString -> HmacKey
hmacKey_init ByteString
seguid
secret :: ByteString
secret =
HmacKey -> PhkdfCtx
phkdfCtx_initFromHmacKey HmacKey
seguidKey PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
[ByteString] -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs [ByteString]
headerUsername PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfCtx -> PhkdfCtx
phkdfCtx_assertBufferPosition Word64
32 PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg ByteString
password PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
[ByteString] -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs [ByteString]
headerLongTag PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg ([ByteString]
-> [ByteString]
-> ByteString
-> ByteString
-> ByteString
-> ByteString
forall (f :: * -> *).
Foldable f =>
f ByteString
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> ByteString
passwordPadding [ByteString]
headerUsername [ByteString]
headerLongTag ByteString
longTag ByteString
domainTag ByteString
password) PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfCtx -> PhkdfCtx
phkdfCtx_assertBufferPosition Word64
32 PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs Vector ByteString
credentials PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg (Vector ByteString -> ByteString -> ByteString -> ByteString
forall (f :: * -> *).
Foldable f =>
f ByteString -> ByteString -> ByteString -> ByteString
credentialsPadding Vector ByteString
credentials ByteString
longTag ByteString
domainTag) PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfCtx -> PhkdfCtx
phkdfCtx_assertBufferPosition Word64
29 PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs Vector ByteString
seedTags PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg (Int -> ByteString
forall b. (Integral b, FiniteBits b) => b -> ByteString
bareEncode (Vector ByteString -> Int
forall a. Vector a -> Int
V.length Vector ByteString
seedTags)) PhkdfCtx -> (PhkdfCtx -> PhkdfSlowCtx) -> PhkdfSlowCtx
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32
-> ByteString
-> ByteString
-> Word32
-> PhkdfCtx
-> PhkdfSlowCtx
phkdfSlowCtx_extract
(ByteString -> Int -> ByteString
cycleByteStringWithNull ByteString
domainTag)
(ByteString -> Word32
word32 ByteString
"go\x00\x00" Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
2023) ByteString
domainTag
ByteString
"phkdf-pass-v0 compact" Word32
rounds PhkdfSlowCtx -> (PhkdfSlowCtx -> PhkdfSlowCtx) -> PhkdfSlowCtx
forall a b. a -> (a -> b) -> b
&
Word64 -> PhkdfSlowCtx -> PhkdfSlowCtx
phkdfSlowCtx_assertBufferPosition Word64
32 PhkdfSlowCtx -> (PhkdfSlowCtx -> PhkdfSlowCtx) -> PhkdfSlowCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx
phkdfSlowCtx_addArgs Vector ByteString
seedTags PhkdfSlowCtx -> (PhkdfSlowCtx -> ByteString) -> ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString) -> PhkdfSlowCtx -> ByteString
phkdfSlowCtx_finalize (ByteString -> Int -> ByteString
cycleByteStringWithNull ByteString
domainTag)
phkdfPass_seedFinalize :: PhkdfSeed -> PhkdfInputTweak -> Stream ByteString
phkdfPass_seedFinalize :: PhkdfSeed -> PhkdfInputTweak -> Stream ByteString
phkdfPass_seedFinalize PhkdfSeed
seed PhkdfInputTweak
tweak = Stream ByteString
echo
where
seguidKey :: HmacKey
seguidKey = PhkdfSeed -> HmacKey
phkdfSeed_seguidKey PhkdfSeed
seed
domainTag :: ByteString
domainTag = PhkdfSeed -> ByteString
phkdfSeed_domainTag PhkdfSeed
seed
secret :: ByteString
secret = PhkdfSeed -> ByteString
phkdfSeed_secret PhkdfSeed
seed
role :: Vector ByteString
role = PhkdfInputTweak -> Vector ByteString
phkdfInputTweak_role PhkdfInputTweak
tweak
echoTag :: ByteString
echoTag = PhkdfInputTweak -> ByteString
phkdfInputTweak_echoTag PhkdfInputTweak
tweak
headerCombine :: ByteString
headerCombine = [ByteString] -> ByteString
B.concat [ByteString
"phkdf-pass-v0 combine", ByteString
secret]
secretKey :: ByteString
secretKey =
HmacKey -> PhkdfCtx
phkdfCtx_initFromHmacKey HmacKey
seguidKey PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArg ByteString
headerCombine PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_addArgs Vector ByteString
role PhkdfCtx -> (PhkdfCtx -> ByteString) -> ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32 -> ByteString -> PhkdfCtx -> ByteString
phkdfCtx_finalize (ByteString -> Int -> ByteString
cycleByteStringWithNull ByteString
domainTag) (ByteString -> Word32
word32 ByteString
"KEY\x00") ByteString
domainTag
headerEcho :: ByteString
headerEcho = ByteString -> Int -> ByteString
cycleByteString (ByteString
domainTag ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"\x00phkdf-pass-v0 echo\x00") Int
32
echo :: Stream ByteString
echo = ByteString -> HmacKey
hmacKey_init ByteString
secretKey HmacKey -> (HmacKey -> PhkdfGen) -> PhkdfGen
forall a b. a -> (a -> b) -> b
&
ByteString -> Word32 -> ByteString -> HmacKey -> PhkdfGen
phkdfGen_initFromHmacKey ByteString
headerEcho (ByteString -> Word32
word32 ByteString
"OUT\x00") ByteString
echoTag PhkdfGen -> (PhkdfGen -> Stream ByteString) -> Stream ByteString
forall a b. a -> (a -> b) -> b
&
PhkdfGen -> Stream ByteString
phkdfGen_finalizeStream