{-# LANGUAGE OverloadedStrings, ViewPatterns #-}
module Crypto.G3P.V2
( g3pHash
, g3pStream
, G3PSalt(..)
, G3PInputs(..)
, G3PSeedInputs(..)
, G3PSpark()
, g3pSpark
, g3pSpark_toSeed
, g3pSpark_toSprout
, g3pSpark_toTree
, g3pSpark_toKey
, g3pSpark_toSource
, g3pSpark_toStream
, G3PSeed()
, g3pSeed
, g3pSeed_fromSpark
, g3pSeed_toSprout
, g3pSeed_toTree
, g3pSeed_toKey
, g3pSeed_toSource
, g3pSeed_toStream
, G3PSprout()
, g3pSprout
, g3pSprout_feedArg
, g3pSprout_feedArgs
, g3pSprout_arg
, g3pSprout_args
, g3pSprout_fromSpark
, g3pSprout_fromSeed
, g3pSprout_toTree
, g3pSprout_toKey
, g3pSprout_toSource
, g3pSprout_toStream
, G3PTree()
, g3pTree
, g3pTree_fromSpark
, g3pTree_fromSeed
, g3pTree_fromSprout
, g3pTree_toKey
, g3pTree_toSource
, g3pTree_toStream
, G3PKey()
, g3pKey
, g3pKey_fromSpark
, g3pKey_fromSeed
, g3pKey_fromSprout
, g3pKey_fromTree
, g3pKey_toSource
, g3pKey_toStream
, G3PSource
, g3pSource
, g3pSource_peek
, g3pSource_read
, g3pSource_fromSpark
, g3pSource_fromSeed
, g3pSource_fromSprout
, g3pSource_fromTree
, g3pSource_fromKey
, g3pSource_toStream
, Stream(..)
, g3pStream_fromSpark
, g3pStream_fromSeed
, g3pStream_fromSprout
, g3pStream_fromTree
, g3pStream_fromKey
, g3pStream_fromSource
, word32
) where
import Data.Bits (xor)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.Function((&))
import Data.Word
import Data.Stream (Stream(..))
import qualified Data.Stream as Stream
import Data.Vector (Vector)
import qualified Data.Vector as V
import Network.ByteOrder (word32, bytestring64)
import Crypto.Encoding.PHKDF
import Crypto.Encoding.SHA3.TupleHash
import Crypto.PHKDF.HMAC
import Crypto.PHKDF
import Crypto.PHKDF.Assert
import Crypto.G3P.BCrypt (bcryptXsFree)
import Crypto.G3P.V2.Subtle
data G3PSalt = G3PSalt
{ G3PSalt -> HmacKey
g3pSalt_seguid :: !HmacKey
, G3PSalt -> ByteString
g3pSalt_longTag :: !ByteString
, G3PSalt -> Vector ByteString
g3pSalt_contextTags :: !(Vector ByteString)
, G3PSalt -> ByteString
g3pSalt_domainTag :: !ByteString
, G3PSalt -> Word32
g3pSalt_phkdfRounds :: !Word32
} deriving (G3PSalt -> G3PSalt -> Bool
(G3PSalt -> G3PSalt -> Bool)
-> (G3PSalt -> G3PSalt -> Bool) -> Eq G3PSalt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: G3PSalt -> G3PSalt -> Bool
== :: G3PSalt -> G3PSalt -> Bool
$c/= :: G3PSalt -> G3PSalt -> Bool
/= :: G3PSalt -> G3PSalt -> Bool
Eq)
data G3PInputs = G3PInputs
{ G3PInputs -> ByteString
g3pInputs_username :: !ByteString
, G3PInputs -> ByteString
g3pInputs_password :: !ByteString
, G3PInputs -> Vector ByteString
g3pInputs_credentials :: !(Vector ByteString)
} deriving (G3PInputs -> G3PInputs -> Bool
(G3PInputs -> G3PInputs -> Bool)
-> (G3PInputs -> G3PInputs -> Bool) -> Eq G3PInputs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: G3PInputs -> G3PInputs -> Bool
== :: G3PInputs -> G3PInputs -> Bool
$c/= :: G3PInputs -> G3PInputs -> Bool
/= :: G3PInputs -> G3PInputs -> Bool
Eq)
data G3PSeedInputs = G3PSeedInputs
{ G3PSeedInputs -> HmacKey
g3pSeedInputs_bcryptSeguid :: !HmacKey
, G3PSeedInputs -> Vector ByteString
g3pSeedInputs_bcryptCredentials :: !(Vector ByteString)
, G3PSeedInputs -> ByteString
g3pSeedInputs_bcryptLongTag :: !ByteString
, G3PSeedInputs -> Vector ByteString
g3pSeedInputs_bcryptContextTags :: !(Vector ByteString)
, G3PSeedInputs -> ByteString
g3pSeedInputs_bcryptDomainTag :: !ByteString
, G3PSeedInputs -> Word32
g3pSeedInputs_bcryptRounds :: !Word32
}
g3pHash
:: Foldable f
=> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
g3pHash :: forall (f :: * -> *).
Foldable f =>
G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
g3pHash = ( ((G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (G3PSalt -> a) -> G3PSalt -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (G3PInputs -> a) -> G3PInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (G3PSeedInputs -> a) -> G3PSeedInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (HmacKey -> a) -> HmacKey -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ByteString
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (f ByteString -> a) -> f ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(((ByteString
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (ByteString
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString -> ByteString -> Word32 -> ByteString -> ByteString)
-> (ByteString
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString -> ByteString -> Word32 -> ByteString -> ByteString)
-> (ByteString
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (ByteString
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString -> Word32 -> ByteString -> ByteString)
-> (ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString -> Word32 -> ByteString -> ByteString)
-> (ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Word32 -> ByteString -> G3PSource)
-> Word32 -> ByteString -> ByteString)
-> (ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Word32 -> ByteString -> G3PSource)
-> Word32 -> ByteString -> ByteString)
-> (ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (Word32 -> ByteString -> G3PSource)
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (ByteString -> Word32 -> ByteString -> G3PSource)
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ByteString -> G3PSource) -> ByteString -> ByteString)
-> (Word32 -> ByteString -> G3PSource)
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> (Word32 -> a) -> Word32 -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((ByteString -> G3PSource) -> ByteString -> ByteString)
-> (Word32 -> ByteString -> G3PSource)
-> Word32
-> ByteString
-> ByteString)
-> ((G3PSource -> ByteString)
-> (ByteString -> G3PSource) -> ByteString -> ByteString)
-> (G3PSource -> ByteString)
-> (Word32 -> ByteString -> G3PSource)
-> Word32
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (G3PSource -> ByteString)
-> (ByteString -> G3PSource) -> ByteString -> ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((G3PSource -> ByteString)
-> (G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString)
-> (G3PSource -> ByteString)
-> (G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> ByteString
forall a b. (a -> b) -> a -> b
$ G3PSource -> ByteString
g3pSource_head) G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall (f :: * -> *).
Foldable f =>
G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSource
g3pSpark
:: G3PSalt
-> G3PInputs
-> G3PSpark
g3pSpark :: G3PSalt -> G3PInputs -> G3PSpark
g3pSpark G3PSalt
salt G3PInputs
inputs = G3PSpark
spark
where
domainTag :: ByteString
domainTag = G3PSalt -> ByteString
g3pSalt_domainTag G3PSalt
salt
seguid :: HmacKey
seguid = G3PSalt -> HmacKey
g3pSalt_seguid G3PSalt
salt
longTag :: ByteString
longTag = G3PSalt -> ByteString
g3pSalt_longTag G3PSalt
salt
contextTags :: Vector ByteString
contextTags = G3PSalt -> Vector ByteString
g3pSalt_contextTags G3PSalt
salt
phkdfRounds :: Word32
phkdfRounds = G3PSalt -> Word32
g3pSalt_phkdfRounds G3PSalt
salt
username :: ByteString
username = G3PInputs -> ByteString
g3pInputs_username G3PInputs
inputs
password :: ByteString
password = G3PInputs -> ByteString
g3pInputs_password G3PInputs
inputs
credentials :: Vector ByteString
credentials = G3PInputs -> Vector ByteString
g3pInputs_credentials G3PInputs
inputs
headerAlfa :: [ByteString]
headerAlfa = [ ByteString
"G3Pb2 alfa username", ByteString
username ]
usernamePadLen :: Int
usernamePadLen = Int
a
where
al :: Int
al = [ByteString] -> Int
forall (f :: * -> *). Foldable f => f ByteString -> Int
encodedVectorByteLength [ByteString]
headerAlfa
a :: Int
a = Int -> Int -> Int
forall a. (Ord a, Num a, Bits a) => a -> a -> a
add64WhileLt (Int
349 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
al) Int
32
usernamePadding :: ByteString
usernamePadding = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$
Int64 -> [ByteString] -> [ByteString]
takeBs (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
usernamePadLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
32)) ([ByteString] -> [ByteString]
forall a. HasCallStack => [a] -> [a]
cycle [ByteString
longTag, ByteString
"\x00"]) [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++
Int64 -> [ByteString] -> [ByteString]
takeBs Int64
32 [ByteString
domainTag, ByteString
"\x00", ByteString
"password G3Pb2", ByteString
nullBuffer]
headerUsername :: [ByteString]
headerUsername = [ByteString]
headerAlfa [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ ByteString
usernamePadding ]
headerLongTag :: [ByteString]
headerLongTag =
[ ByteString
longTag
, [ByteString] -> ByteString
B.concat
[ Word32 -> ByteString
forall b. (Integral b, FiniteBits b) => b -> ByteString
bareEncode Word32
phkdfRounds
, ByteString
"Global Password Prehash Protocol bcryptXsFree v2 G3Pb2"
]
]
passwordPadLen :: Int
passwordPadLen = Int
c
where
al :: Int
al = [ByteString] -> Int
forall (f :: * -> *). Foldable f => f ByteString -> Int
encodedVectorByteLength [ByteString]
headerLongTag
a :: Int
a = Int -> Int -> Int
forall a. (Ord a, Num a, Bits a) => a -> a -> a
add64WhileLt (Int
8605 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
al) Int
4449
bl :: Int
bl = [ByteString] -> Int
forall (f :: * -> *). Foldable f => f ByteString -> Int
encodedVectorByteLength [ByteString]
headerUsername
b :: Int
b = Int -> Int -> Int
forall a. (Ord a, Num a, Bits a) => a -> a -> a
add64WhileLt (Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
bl) Int
328
cl :: Int
cl = ByteString -> Int
encodedByteLength ByteString
password
c :: Int
c = Int -> Int -> Int
forall a. (Ord a, Num a, Bits a) => a -> a -> a
add64WhileLt (Int
b Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
cl) Int
32
longPadding :: [ByteString]
longPadding =
Int64 -> [ByteString] -> [ByteString]
takeBs (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
passwordPadLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
32)) ([ByteString] -> [ByteString]
forall a. HasCallStack => [a] -> [a]
cycle [ByteString
longTag, ByteString
"\x00"]) [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++
Int64 -> [ByteString] -> [ByteString]
takeBs Int64
32 [ByteString
domainTag, ByteString
"\x00", ByteString
"creds G3Pb2", ByteString
nullBuffer]
credsPadLen :: Int
credsPadLen = Int
a
where
al :: Int
al = Vector ByteString -> Int
forall (f :: * -> *). Foldable f => f ByteString -> Int
encodedVectorByteLength Vector ByteString
credentials
a :: Int
a = Int -> Int -> Int
forall a. (Ord a, Num a, Bits a) => a -> a -> a
add64WhileLt (Int
314 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
al) Int
32
credsPadding :: [ByteString]
credsPadding =
Int64 -> [ByteString] -> [ByteString]
takeBs (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
credsPadLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
29)) ([ByteString] -> [ByteString]
forall a. HasCallStack => [a] -> [a]
cycle [ByteString
longTag, ByteString
"\x00"]) [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++
Int64 -> [ByteString] -> [ByteString]
takeBs Int64
29 [ByteString
domainTag, ByteString
"\x00", ByteString
"tags G3Pb2", ByteString
nullBuffer]
(PairBS ByteString
alfaSum ByteString
alfaExt) =
HmacKey -> PhkdfCtx
phkdfCtx_init HmacKey
seguid PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
[ByteString] -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArgs [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_feedArg 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_feedArgs [ByteString]
headerLongTag PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
[ByteString] -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArgConcat [ByteString]
longPadding 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_feedArgs Vector ByteString
credentials PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
[ByteString] -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArgConcat [ByteString]
credsPadding 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_feedArgs Vector ByteString
contextTags PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArg (Int -> ByteString
forall b. (Integral b, FiniteBits b) => b -> ByteString
bareEncode (Vector ByteString -> Int
forall a. Vector a -> Int
V.length Vector ByteString
contextTags)) PhkdfCtx -> (PhkdfCtx -> Stream ByteString) -> Stream ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32 -> ByteString -> PhkdfCtx -> Stream ByteString
phkdfCtx_toStream Int -> ByteString
endPadding
(ByteString -> Word32
word32 ByteString
"go\x00\x00" Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
2024) ByteString
domainTag Stream ByteString
-> (Stream ByteString -> Stream PairBS) -> Stream PairBS
forall a b. a -> (a -> b) -> b
&
Stream ByteString -> Stream PairBS
xorScan Stream PairBS -> (Stream PairBS -> Stream PairBS) -> Stream PairBS
forall a b. a -> (a -> b) -> b
& Word32 -> Stream PairBS -> Stream PairBS
forall a. Word32 -> Stream a -> Stream a
myDrop' Word32
1 Stream PairBS -> (Stream PairBS -> Stream PairBS) -> Stream PairBS
forall a b. a -> (a -> b) -> b
&
Word32 -> Stream PairBS -> Stream PairBS
forall a. Word32 -> Stream a -> Stream a
myDrop' Word32
phkdfRounds Stream PairBS -> (Stream PairBS -> PairBS) -> PairBS
forall a b. a -> (a -> b) -> b
&
Stream PairBS -> PairBS
forall a. Stream a -> a
Stream.head
endPadding :: Int -> ByteString
endPadding = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> (Int -> [ByteString]) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int64 -> [ByteString] -> [ByteString])
-> [ByteString] -> Int64 -> [ByteString]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int64 -> [ByteString] -> [ByteString]
takeBs ([ByteString] -> [ByteString]
forall a. HasCallStack => [a] -> [a]
cycle [ByteString
longTag, ByteString
"\x00"]) (Int64 -> [ByteString]) -> (Int -> Int64) -> Int -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
bravo :: ByteString
bravo = ByteString
"G3Pb2 bravo"
headerBravo :: [ByteString]
headerBravo =
[ ByteString
bravo, ByteString
alfaExt ] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ Int64 -> [ByteString] -> [ByteString]
takeBs Int64
53 ([ByteString] -> [ByteString]
forall a. HasCallStack => [a] -> [a]
cycle [ByteString
longTag, ByteString
"\x00"]) [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++
[ ByteString
alfaSum ]
(ByteString
"",HmacKeyPrefixed
prefixBravo) = HmacKey -> HmacKeyPrefixed
hmacKeyPrefixed_init HmacKey
seguid HmacKeyPrefixed
-> (HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed))
-> (ByteString, HmacKeyPrefixed)
forall a b. a -> (a -> b) -> b
&
[ByteString] -> HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed)
forall (f :: * -> *).
Foldable f =>
f ByteString -> HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed)
hmacKeyPrefixed_feeds [ByteString]
headerBravo
bravoKeyPad :: ByteString -> ByteString
bravoKeyPad ByteString
b = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$
Int64 -> [ByteString] -> [ByteString]
takeBs Int64
31 [ByteString
domainTag, ByteString
"\x00", ByteString
bravo, ByteString
nullBuffer] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString
b]
keyB :: ByteString
keyB = ByteString -> HmacKeyPrefixed -> PhkdfCtx
phkdfCtx_initPrefixed (ByteString -> ByteString
bravoKeyPad ByteString
"B") HmacKeyPrefixed
prefixBravo PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArgs Vector ByteString
contextTags PhkdfCtx -> (PhkdfCtx -> ByteString) -> ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32 -> ByteString -> PhkdfCtx -> ByteString
phkdfCtx_finalize Int -> ByteString
endPadding (ByteString -> Word32
word32 ByteString
"KEYB") ByteString
domainTag
keyC :: ByteString
keyC = ByteString -> HmacKeyPrefixed -> PhkdfCtx
phkdfCtx_initPrefixed (ByteString -> ByteString
bravoKeyPad ByteString
"C") HmacKeyPrefixed
prefixBravo PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArgs Vector ByteString
contextTags PhkdfCtx -> (PhkdfCtx -> ByteString) -> ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32 -> ByteString -> PhkdfCtx -> ByteString
phkdfCtx_finalize Int -> ByteString
endPadding (ByteString -> Word32
word32 ByteString
"KEYC") ByteString
domainTag
spark :: G3PSpark
spark = G3PSpark
{ g3pSpark_beginKey :: ByteString
g3pSpark_beginKey = ByteString
keyB
, g3pSpark_contKey :: ByteString
g3pSpark_contKey = ByteString
keyC
, g3pSpark_contextTags :: Vector ByteString
g3pSpark_contextTags = Vector ByteString
contextTags
, g3pSpark_domainTag :: ByteString
g3pSpark_domainTag = ByteString
domainTag
}
myDrop' :: Word32 -> Stream a -> Stream a
myDrop' :: forall a. Word32 -> Stream a -> Stream a
myDrop' = Word32 -> Stream a -> Stream a
forall {t} {a}. (Eq t, Num t) => t -> Stream a -> Stream a
go
where
go :: t -> Stream a -> Stream a
go t
0 Stream a
s = Stream a
s
go t
n (Cons a
x Stream a
s) = a
x a -> Stream a -> Stream a
forall a b. a -> b -> b
`seq` t -> Stream a -> Stream a
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) Stream a
s
xorBS :: ByteString -> ByteString -> ByteString
xorBS :: ByteString -> ByteString -> ByteString
xorBS = (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
B.packZipWith Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
xor
data PairBS = PairBS !ByteString !ByteString
xorScan :: Stream ByteString -> Stream PairBS
xorScan :: Stream ByteString -> Stream PairBS
xorScan = Stream PairBS -> Stream PairBS
forall a. Stream a -> Stream a
Stream.tail (Stream PairBS -> Stream PairBS)
-> (Stream ByteString -> Stream PairBS)
-> Stream ByteString
-> Stream PairBS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PairBS -> ByteString -> PairBS)
-> PairBS -> Stream ByteString -> Stream PairBS
forall a b. (a -> b -> a) -> a -> Stream b -> Stream a
Stream.scan' PairBS -> ByteString -> PairBS
f (ByteString -> ByteString -> PairBS
PairBS ByteString
blankChunk ByteString
blankChunk)
where f :: PairBS -> ByteString -> PairBS
f (PairBS ByteString
acc ByteString
old) ByteString
new = ByteString -> ByteString -> PairBS
PairBS (ByteString -> ByteString -> ByteString
xorBS ByteString
acc ByteString
old) ByteString
new
blankChunk :: ByteString
blankChunk = Int -> Word8 -> ByteString
B.replicate Int
32 Word8
0
g3pSpark_toSeed
:: G3PSpark
-> G3PSeedInputs
-> G3PSeed
g3pSpark_toSeed :: G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed G3PSpark
spark G3PSeedInputs
inputs = ByteString -> G3PSeed
G3PSeed ByteString
seed
where
beginKey :: ByteString
beginKey = G3PSpark -> ByteString
g3pSpark_beginKey G3PSpark
spark
contKey :: ByteString
contKey = G3PSpark -> ByteString
g3pSpark_contKey G3PSpark
spark
contextTags :: Vector ByteString
contextTags = G3PSpark -> Vector ByteString
g3pSpark_contextTags G3PSpark
spark
domainTag :: ByteString
domainTag = G3PSpark -> ByteString
g3pSpark_domainTag G3PSpark
spark
bSeguid :: HmacKey
bSeguid = G3PSeedInputs -> HmacKey
g3pSeedInputs_bcryptSeguid G3PSeedInputs
inputs
bCreds :: Vector ByteString
bCreds = G3PSeedInputs -> Vector ByteString
g3pSeedInputs_bcryptCredentials G3PSeedInputs
inputs
bRounds :: Word32
bRounds = G3PSeedInputs -> Word32
g3pSeedInputs_bcryptRounds G3PSeedInputs
inputs
bLongTag :: ByteString
bLongTag = G3PSeedInputs -> ByteString
g3pSeedInputs_bcryptLongTag G3PSeedInputs
inputs
bDomainTag :: ByteString
bDomainTag = G3PSeedInputs -> ByteString
g3pSeedInputs_bcryptDomainTag G3PSeedInputs
inputs
bContextTags :: Vector ByteString
bContextTags = G3PSeedInputs -> Vector ByteString
g3pSeedInputs_bcryptContextTags G3PSeedInputs
inputs
charlie :: ByteString
charlie = ByteString
"G3Pb2 charlie"
charlieHeader :: [ByteString]
charlieHeader = ByteString
charlie ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString
beginKey ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: Int64 -> [ByteString] -> [ByteString]
takeBs Int64
19 [ByteString
domainTag, ByteString
nullBuffer]
(ByteString
"", HmacKeyPrefixed
charliePrefix) =
HmacKey -> HmacKeyPrefixed
hmacKeyPrefixed_init HmacKey
bSeguid HmacKeyPrefixed
-> (HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed))
-> (ByteString, HmacKeyPrefixed)
forall a b. a -> (a -> b) -> b
&
[ByteString] -> HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed)
forall (f :: * -> *).
Foldable f =>
f ByteString -> HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed)
hmacKeyPrefixed_feeds [ByteString]
charlieHeader
bcryptName :: ByteString
bcryptName = [ByteString] -> ByteString
B.concat
[ ByteString
"G3Pb2 bcrypt-xs-free"
, Word64 -> ByteString
bytestring64 (Word64
8 Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
B.length ByteString
bLongTag))
]
(Int
_, HmacKeyPrefixed
charlieCont) =
(ByteString -> ByteString)
-> ByteString
-> Vector ByteString
-> ByteString
-> Vector ByteString
-> ByteString
-> Word32
-> HmacKeyPrefixed
-> (Int, HmacKeyPrefixed)
forall (f :: * -> *) a.
Foldable f =>
(a -> ByteString)
-> ByteString
-> f a
-> ByteString
-> f a
-> ByteString
-> Word32
-> HmacKeyPrefixed
-> (Int, HmacKeyPrefixed)
bcryptXsFree ByteString -> ByteString
forall a. a -> a
id ByteString
bcryptName Vector ByteString
bCreds ByteString
bLongTag Vector ByteString
bContextTags ByteString
bDomainTag
Word32
bRounds HmacKeyPrefixed
charliePrefix
contPad :: ByteString
contPad = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ Int64 -> [ByteString] -> [ByteString]
takeBs Int64
32 [ByteString
domainTag, ByteString
"\x00", ByteString
charlie, ByteString
nullBuffer]
(ByteString
"", HmacKeyPrefixed
endCont) = [ByteString] -> HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed)
forall (f :: * -> *).
Foldable f =>
f ByteString -> HmacKeyPrefixed -> (ByteString, HmacKeyPrefixed)
hmacKeyPrefixed_feeds [ByteString
contPad, ByteString
contKey] HmacKeyPrefixed
charlieCont
seed :: ByteString
seed = ByteString -> HmacKeyPrefixed -> PhkdfCtx
phkdfCtx_initPrefixed ByteString
contPad HmacKeyPrefixed
endCont PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
Vector ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArgs Vector ByteString
contextTags PhkdfCtx -> (PhkdfCtx -> ByteString) -> ByteString
forall a b. a -> (a -> b) -> b
&
(Int -> ByteString)
-> Word32 -> ByteString -> PhkdfCtx -> ByteString
phkdfCtx_finalize Int -> ByteString
endPadding (ByteString -> Word32
word32 ByteString
"SEED") ByteString
domainTag
endPadding :: Int -> ByteString
endPadding = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> (Int -> [ByteString]) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int64 -> [ByteString] -> [ByteString])
-> [ByteString] -> Int64 -> [ByteString]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int64 -> [ByteString] -> [ByteString]
takeBs ([ByteString] -> [ByteString]
forall a. HasCallStack => [a] -> [a]
cycle [ByteString
domainTag, ByteString
"\x00"]) (Int64 -> [ByteString]) -> (Int -> Int64) -> Int -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
g3pSeed_toSprout
:: G3PSeed
-> HmacKey
-> G3PSprout
g3pSeed_toSprout :: G3PSeed -> HmacKey -> G3PSprout
g3pSeed_toSprout (G3PSeed ByteString
seed) HmacKey
key = PhkdfCtx -> G3PSprout
G3PSprout PhkdfCtx
ctx
where
delta :: ByteString
delta = ByteString
"G3Pb2 delta"
ctx :: PhkdfCtx
ctx = HmacKey -> PhkdfCtx
phkdfCtx_init HmacKey
key PhkdfCtx -> (PhkdfCtx -> PhkdfCtx) -> PhkdfCtx
forall a b. a -> (a -> b) -> b
&
ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArg (ByteString
delta ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
seed)
g3pSprout_feedArg
:: ByteString
-> G3PSprout
-> G3PSprout
g3pSprout_feedArg :: ByteString -> G3PSprout -> G3PSprout
g3pSprout_feedArg ByteString
x = PhkdfCtx -> G3PSprout
G3PSprout (PhkdfCtx -> G3PSprout)
-> (G3PSprout -> PhkdfCtx) -> G3PSprout -> G3PSprout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArg ByteString
x (PhkdfCtx -> PhkdfCtx)
-> (G3PSprout -> PhkdfCtx) -> G3PSprout -> PhkdfCtx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> PhkdfCtx
g3pSprout_phkdfCtx
g3pSprout_feedArgs
:: Foldable f
=> f ByteString
-> G3PSprout
-> G3PSprout
g3pSprout_feedArgs :: forall (f :: * -> *).
Foldable f =>
f ByteString -> G3PSprout -> G3PSprout
g3pSprout_feedArgs f ByteString
xs = PhkdfCtx -> G3PSprout
G3PSprout (PhkdfCtx -> G3PSprout)
-> (G3PSprout -> PhkdfCtx) -> G3PSprout -> G3PSprout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f ByteString -> PhkdfCtx -> PhkdfCtx
forall (f :: * -> *).
Foldable f =>
f ByteString -> PhkdfCtx -> PhkdfCtx
phkdfCtx_feedArgs f ByteString
xs (PhkdfCtx -> PhkdfCtx)
-> (G3PSprout -> PhkdfCtx) -> G3PSprout -> PhkdfCtx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> PhkdfCtx
g3pSprout_phkdfCtx
g3pSprout_arg
:: G3PSprout
-> ByteString
-> G3PSprout
g3pSprout_arg :: G3PSprout -> ByteString -> G3PSprout
g3pSprout_arg = (ByteString -> G3PSprout -> G3PSprout)
-> G3PSprout -> ByteString -> G3PSprout
forall a b c. (a -> b -> c) -> b -> a -> c
flip ByteString -> G3PSprout -> G3PSprout
g3pSprout_feedArg
g3pSprout_args
:: Foldable f
=> G3PSprout
-> f ByteString
-> G3PSprout
g3pSprout_args :: forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> G3PSprout
g3pSprout_args = (f ByteString -> G3PSprout -> G3PSprout)
-> G3PSprout -> f ByteString -> G3PSprout
forall a b c. (a -> b -> c) -> b -> a -> c
flip f ByteString -> G3PSprout -> G3PSprout
forall (f :: * -> *).
Foldable f =>
f ByteString -> G3PSprout -> G3PSprout
g3pSprout_feedArgs
g3pSprout_toTree
:: G3PSprout
-> ByteString
-> G3PTree
g3pSprout_toTree :: G3PSprout -> ByteString -> G3PTree
g3pSprout_toTree (G3PSprout PhkdfCtx
ctx) ByteString
domainTag = ByteString -> G3PTree
G3PTree ByteString
key
where
key :: ByteString
key = (Int -> ByteString)
-> Word32 -> ByteString -> PhkdfCtx -> ByteString
phkdfCtx_finalize Int -> ByteString
endPadding (ByteString -> Word32
word32 ByteString
"KEYL") ByteString
domainTag PhkdfCtx
ctx
endPadding :: Int -> ByteString
endPadding = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> (Int -> [ByteString]) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int64 -> [ByteString] -> [ByteString])
-> [ByteString] -> Int64 -> [ByteString]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int64 -> [ByteString] -> [ByteString]
takeBs ([ByteString] -> [ByteString]
forall a. HasCallStack => [a] -> [a]
cycle [ByteString
domainTag, ByteString
"\x00"]) (Int64 -> [ByteString]) -> (Int -> Int64) -> Int -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
g3pTree_toKey
:: G3PTree
-> ByteString
-> G3PKey
g3pTree_toKey :: G3PTree -> ByteString -> G3PKey
g3pTree_toKey (G3PTree ByteString
echoKeyL) ByteString
echoKeyR = HmacKeyHashed -> G3PKey
G3PKey (ByteString -> HmacKeyHashed
hmacKeyHashed ByteString
key)
where
keyR :: [ByteString]
keyR = Int64 -> [ByteString] -> [ByteString]
takeBs Int64
32 [ByteString
echoKeyR, ByteString
"\x00", ByteString
"G3Pb2 echo key right padding", ByteString
nullBuffer]
keyL :: [ByteString]
keyL = Int64 -> [ByteString] -> [ByteString]
takeBs Int64
32 [ByteString
echoKeyL, ByteString
nullBuffer]
key :: ByteString
key = [ByteString] -> ByteString
B.concat ([ByteString]
keyL [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString]
keyR)
g3pKey_toSource
:: G3PKey
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pKey_toSource :: G3PKey -> ByteString -> Word32 -> ByteString -> G3PSource
g3pKey_toSource (G3PKey HmacKeyHashed
key) ByteString
echoHeader Word32
echoCtr ByteString
echoTag = G3PSource
gen
where
hdr :: ByteString
hdr = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$
Int64 -> [ByteString] -> [ByteString]
takeBs Int64
32 [ByteString
echoHeader, ByteString
"\x00", ByteString
"G3Pb2 echo header padding", ByteString
nullBuffer]
gen :: G3PSource
gen = HmacKeyHashed -> ByteString -> Word32 -> ByteString -> G3PSource
phkdfGen_initHashed HmacKeyHashed
key ByteString
hdr Word32
echoCtr ByteString
echoTag
g3pSource_head :: G3PSource -> ByteString
g3pSource_head :: G3PSource -> ByteString
g3pSource_head = (ByteString, G3PSource) -> ByteString
forall a b. (a, b) -> a
fst ((ByteString, G3PSource) -> ByteString)
-> (G3PSource -> (ByteString, G3PSource))
-> G3PSource
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSource -> (ByteString, G3PSource)
phkdfGen_read
g3pSource_read :: G3PSource -> (ByteString, G3PSource)
g3pSource_read :: G3PSource -> (ByteString, G3PSource)
g3pSource_read = G3PSource -> (ByteString, G3PSource)
phkdfGen_read
g3pSource_peek :: G3PSource -> Maybe ByteString
g3pSource_peek :: G3PSource -> Maybe ByteString
g3pSource_peek = G3PSource -> Maybe ByteString
phkdfGen_peek
g3pSource_toStream :: G3PSource -> Stream ByteString
g3pSource_toStream :: G3PSource -> Stream ByteString
g3pSource_toStream = G3PSource -> Stream ByteString
phkdfGen_toStream
type G3PSource = PhkdfGen
g3pKey_toStream
:: G3PKey
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pKey_toStream :: G3PKey -> ByteString -> Word32 -> ByteString -> Stream ByteString
g3pKey_toStream G3PKey
key ByteString
hdr Word32
ctr ByteString
tag =
G3PSource -> Stream ByteString
phkdfGen_toStream (G3PKey -> ByteString -> Word32 -> ByteString -> G3PSource
g3pKey_toSource G3PKey
key ByteString
hdr Word32
ctr ByteString
tag)
g3pTree_toStream
:: G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pTree_toStream :: G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pTree_toStream = (G3PKey -> ByteString -> Word32 -> ByteString -> Stream ByteString)
-> (ByteString -> G3PKey)
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PKey -> ByteString -> Word32 -> ByteString -> Stream ByteString
g3pKey_toStream ((ByteString -> G3PKey)
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PTree -> ByteString -> G3PKey)
-> G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PTree -> ByteString -> G3PKey
g3pTree_toKey
g3pSprout_toStream
:: Foldable f
=> G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSprout_toStream :: forall (f :: * -> *).
Foldable f =>
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSprout_toStream =
(G3PSprout
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (f ByteString -> G3PSprout)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall a b. (a -> b) -> (f ByteString -> a) -> f ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (ByteString -> G3PTree)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pTree_toStream ((ByteString -> G3PTree)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PSprout -> ByteString -> G3PTree)
-> G3PSprout
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> ByteString -> G3PTree
g3pSprout_toTree) ((f ByteString -> G3PSprout)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PSprout -> f ByteString -> G3PSprout)
-> G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> f ByteString -> G3PSprout
forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> G3PSprout
g3pSprout_args
g3pSeed_toStream
:: Foldable f
=> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSeed_toStream :: forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSeed_toStream = (G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (HmacKey -> G3PSprout)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall a b. (a -> b) -> (HmacKey -> a) -> HmacKey -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall (f :: * -> *).
Foldable f =>
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSprout_toStream ((HmacKey -> G3PSprout)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PSeed -> HmacKey -> G3PSprout)
-> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSeed -> HmacKey -> G3PSprout
g3pSeed_toSprout
g3pSpark_toStream
:: Foldable f
=> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSpark_toStream :: forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSpark_toStream = (G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall a b. (a -> b) -> (G3PSeedInputs -> a) -> G3PSeedInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSeed_toStream ((G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed
g3pSpark_toSprout
:: G3PSpark
-> G3PSeedInputs
-> HmacKey
-> G3PSprout
g3pSpark_toSprout :: G3PSpark -> G3PSeedInputs -> HmacKey -> G3PSprout
g3pSpark_toSprout = (G3PSeed -> HmacKey -> G3PSprout)
-> (G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> G3PSprout
forall a b. (a -> b) -> (G3PSeedInputs -> a) -> G3PSeedInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSeed -> HmacKey -> G3PSprout
g3pSeed_toSprout ((G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs -> HmacKey -> G3PSprout)
-> (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> G3PSprout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed
g3pSpark_toTree
:: Foldable f
=> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
g3pSpark_toTree :: forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
g3pSpark_toTree = (G3PSeed -> HmacKey -> f ByteString -> ByteString -> G3PTree)
-> (G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall a b. (a -> b) -> (G3PSeedInputs -> a) -> G3PSeedInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSeed -> HmacKey -> f ByteString -> ByteString -> G3PTree
forall (f :: * -> *).
Foldable f =>
G3PSeed -> HmacKey -> f ByteString -> ByteString -> G3PTree
g3pSeed_toTree ((G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree)
-> (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed
g3pSpark_toKey
:: Foldable f
=> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pSpark_toKey :: forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pSpark_toKey = (G3PSeed
-> HmacKey -> f ByteString -> ByteString -> ByteString -> G3PKey)
-> (G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall a b. (a -> b) -> (G3PSeedInputs -> a) -> G3PSeedInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSeed
-> HmacKey -> f ByteString -> ByteString -> ByteString -> G3PKey
forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey -> f ByteString -> ByteString -> ByteString -> G3PKey
g3pSeed_toKey ((G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey)
-> (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed
g3pSpark_toSource
:: Foldable f
=> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSpark_toSource :: forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSpark_toSource = (G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall a b. (a -> b) -> (G3PSeedInputs -> a) -> G3PSeedInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSeed_toSource ((G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed
g3pSeed
:: G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> G3PSeed
g3pSeed :: G3PSalt -> G3PInputs -> G3PSeedInputs -> G3PSeed
g3pSeed = (((G3PInputs -> G3PSpark) -> G3PInputs -> G3PSeedInputs -> G3PSeed)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> G3PSeed
forall a b. (a -> b) -> (G3PSalt -> a) -> G3PSalt -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((G3PInputs -> G3PSpark) -> G3PInputs -> G3PSeedInputs -> G3PSeed)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> G3PSeed)
-> ((G3PSpark -> G3PSeedInputs -> G3PSeed)
-> (G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> G3PSeed)
-> (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> G3PSeed
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> (G3PInputs -> G3PSpark) -> G3PInputs -> G3PSeedInputs -> G3PSeed
forall a b. (a -> b) -> (G3PInputs -> a) -> G3PInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((G3PSpark -> G3PSeedInputs -> G3PSeed)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> G3PSeed)
-> (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> G3PSeed
forall a b. (a -> b) -> a -> b
$ G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed) G3PSalt -> G3PInputs -> G3PSpark
g3pSpark
g3pSeed_fromSpark
:: G3PSeedInputs
-> G3PSpark
-> G3PSeed
g3pSeed_fromSpark :: G3PSeedInputs -> G3PSpark -> G3PSeed
g3pSeed_fromSpark = (G3PSpark -> G3PSeedInputs -> G3PSeed)
-> G3PSeedInputs -> G3PSpark -> G3PSeed
forall a b c. (a -> b -> c) -> b -> a -> c
flip G3PSpark -> G3PSeedInputs -> G3PSeed
g3pSpark_toSeed
g3pSeed_toTree
:: Foldable f
=> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
g3pSeed_toTree :: forall (f :: * -> *).
Foldable f =>
G3PSeed -> HmacKey -> f ByteString -> ByteString -> G3PTree
g3pSeed_toTree = (G3PSprout -> f ByteString -> ByteString -> G3PTree)
-> (HmacKey -> G3PSprout)
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall a b. (a -> b) -> (HmacKey -> a) -> HmacKey -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((G3PSprout -> ByteString -> G3PTree)
-> (f ByteString -> G3PSprout)
-> f ByteString
-> ByteString
-> G3PTree
forall a b. (a -> b) -> (f ByteString -> a) -> f ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSprout -> ByteString -> G3PTree
g3pSprout_toTree ((f ByteString -> G3PSprout)
-> f ByteString -> ByteString -> G3PTree)
-> (G3PSprout -> f ByteString -> G3PSprout)
-> G3PSprout
-> f ByteString
-> ByteString
-> G3PTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> f ByteString -> G3PSprout
forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> G3PSprout
g3pSprout_args) ((HmacKey -> G3PSprout)
-> HmacKey -> f ByteString -> ByteString -> G3PTree)
-> (G3PSeed -> HmacKey -> G3PSprout)
-> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSeed -> HmacKey -> G3PSprout
g3pSeed_toSprout
g3pSeed_toKey
:: Foldable f
=> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pSeed_toKey :: forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey -> f ByteString -> ByteString -> ByteString -> G3PKey
g3pSeed_toKey = (G3PSprout -> f ByteString -> ByteString -> ByteString -> G3PKey)
-> (HmacKey -> G3PSprout)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall a b. (a -> b) -> (HmacKey -> a) -> HmacKey -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSprout -> f ByteString -> ByteString -> ByteString -> G3PKey
forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> ByteString -> ByteString -> G3PKey
g3pSprout_toKey ((HmacKey -> G3PSprout)
-> HmacKey -> f ByteString -> ByteString -> ByteString -> G3PKey)
-> (G3PSeed -> HmacKey -> G3PSprout)
-> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSeed -> HmacKey -> G3PSprout
g3pSeed_toSprout
g3pSeed_toSource
:: Foldable f
=> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSeed_toSource :: forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSeed_toSource = (G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (HmacKey -> G3PSprout)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall a b. (a -> b) -> (HmacKey -> a) -> HmacKey -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall (f :: * -> *).
Foldable f =>
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSprout_toSource ((HmacKey -> G3PSprout)
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (G3PSeed -> HmacKey -> G3PSprout)
-> G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSeed -> HmacKey -> G3PSprout
g3pSeed_toSprout
g3pSprout
:: G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> G3PSprout
g3pSprout :: G3PSalt -> G3PInputs -> G3PSeedInputs -> HmacKey -> G3PSprout
g3pSprout = (G3PSpark -> G3PSeedInputs -> HmacKey -> G3PSprout)
-> (G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> G3PSprout
forall a b. (a -> b) -> (G3PInputs -> a) -> G3PInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSpark -> G3PSeedInputs -> HmacKey -> G3PSprout
g3pSpark_toSprout ((G3PInputs -> G3PSpark)
-> G3PInputs -> G3PSeedInputs -> HmacKey -> G3PSprout)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> G3PSprout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSalt -> G3PInputs -> G3PSpark
g3pSpark
g3pSprout_fromSpark
:: G3PSeedInputs
-> HmacKey
-> G3PSpark
-> G3PSprout
g3pSprout_fromSpark :: G3PSeedInputs -> HmacKey -> G3PSpark -> G3PSprout
g3pSprout_fromSpark G3PSeedInputs
inputs HmacKey
key G3PSpark
spark =
G3PSpark -> G3PSeedInputs -> HmacKey -> G3PSprout
g3pSpark_toSprout G3PSpark
spark G3PSeedInputs
inputs HmacKey
key
g3pSprout_fromSeed
:: HmacKey
-> G3PSeed -> G3PSprout
g3pSprout_fromSeed :: HmacKey -> G3PSeed -> G3PSprout
g3pSprout_fromSeed = (G3PSeed -> HmacKey -> G3PSprout)
-> HmacKey -> G3PSeed -> G3PSprout
forall a b c. (a -> b -> c) -> b -> a -> c
flip G3PSeed -> HmacKey -> G3PSprout
g3pSeed_toSprout
g3pSprout_toKey
:: Foldable f
=> G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pSprout_toKey :: forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> ByteString -> ByteString -> G3PKey
g3pSprout_toKey = (G3PSprout -> ByteString -> ByteString -> G3PKey)
-> (f ByteString -> G3PSprout)
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall a b. (a -> b) -> (f ByteString -> a) -> f ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((G3PTree -> ByteString -> G3PKey)
-> (ByteString -> G3PTree) -> ByteString -> ByteString -> G3PKey
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PTree -> ByteString -> G3PKey
g3pTree_toKey ((ByteString -> G3PTree) -> ByteString -> ByteString -> G3PKey)
-> (G3PSprout -> ByteString -> G3PTree)
-> G3PSprout
-> ByteString
-> ByteString
-> G3PKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> ByteString -> G3PTree
g3pSprout_toTree) ((f ByteString -> G3PSprout)
-> f ByteString -> ByteString -> ByteString -> G3PKey)
-> (G3PSprout -> f ByteString -> G3PSprout)
-> G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> f ByteString -> G3PSprout
forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> G3PSprout
g3pSprout_args
g3pSprout_toSource
:: Foldable f
=> G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSprout_toSource :: forall (f :: * -> *).
Foldable f =>
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSprout_toSource =
(G3PSprout
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (f ByteString -> G3PSprout)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall a b. (a -> b) -> (f ByteString -> a) -> f ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((G3PTree
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> (ByteString -> G3PTree)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PTree
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource
g3pTree_toSource ((ByteString -> G3PTree)
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (G3PSprout -> ByteString -> G3PTree)
-> G3PSprout
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> ByteString -> G3PTree
g3pSprout_toTree) ((f ByteString -> G3PSprout)
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (G3PSprout -> f ByteString -> G3PSprout)
-> G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSprout -> f ByteString -> G3PSprout
forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> G3PSprout
g3pSprout_args
g3pTree
:: Foldable f
=> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
g3pTree :: forall (f :: * -> *).
Foldable f =>
G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
g3pTree = (G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree)
-> (G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall a b. (a -> b) -> (G3PInputs -> a) -> G3PInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
g3pSpark_toTree ((G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSalt -> G3PInputs -> G3PSpark
g3pSpark
g3pTree_fromSpark
:: Foldable f
=> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PSpark
-> G3PTree
g3pTree_fromSpark :: forall (f :: * -> *).
Foldable f =>
G3PSeedInputs
-> HmacKey -> f ByteString -> ByteString -> G3PSpark -> G3PTree
g3pTree_fromSpark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag G3PSpark
spark =
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> G3PTree
g3pSpark_toTree G3PSpark
spark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag
g3pTree_fromSeed
:: Foldable f
=> HmacKey
-> f ByteString
-> ByteString
-> G3PSeed
-> G3PTree
g3pTree_fromSeed :: forall (f :: * -> *).
Foldable f =>
HmacKey -> f ByteString -> ByteString -> G3PSeed -> G3PTree
g3pTree_fromSeed HmacKey
key f ByteString
role ByteString
tag G3PSeed
seed =
G3PSeed -> HmacKey -> f ByteString -> ByteString -> G3PTree
forall (f :: * -> *).
Foldable f =>
G3PSeed -> HmacKey -> f ByteString -> ByteString -> G3PTree
g3pSeed_toTree G3PSeed
seed HmacKey
key f ByteString
role ByteString
tag
g3pTree_fromSprout
:: ByteString
-> G3PSprout -> G3PTree
g3pTree_fromSprout :: ByteString -> G3PSprout -> G3PTree
g3pTree_fromSprout = (G3PSprout -> ByteString -> G3PTree)
-> ByteString -> G3PSprout -> G3PTree
forall a b c. (a -> b -> c) -> b -> a -> c
flip G3PSprout -> ByteString -> G3PTree
g3pSprout_toTree
g3pTree_toSource
:: G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pTree_toSource :: G3PTree
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource
g3pTree_toSource = (G3PKey -> ByteString -> Word32 -> ByteString -> G3PSource)
-> (ByteString -> G3PKey)
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PKey -> ByteString -> Word32 -> ByteString -> G3PSource
g3pKey_toSource ((ByteString -> G3PKey)
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource)
-> (G3PTree -> ByteString -> G3PKey)
-> G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PTree -> ByteString -> G3PKey
g3pTree_toKey
g3pKey
:: Foldable f
=> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pKey :: forall (f :: * -> *).
Foldable f =>
G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pKey = (G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey)
-> (G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall a b. (a -> b) -> (G3PInputs -> a) -> G3PInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pSpark_toKey ((G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSalt -> G3PInputs -> G3PSpark
g3pSpark
g3pKey_fromSpark
:: Foldable f
=> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PSpark
-> G3PKey
g3pKey_fromSpark :: forall (f :: * -> *).
Foldable f =>
G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PSpark
-> G3PKey
g3pKey_fromSpark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag ByteString
ekey G3PSpark
spark =
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PKey
g3pSpark_toKey G3PSpark
spark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag ByteString
ekey
g3pKey_fromSeed
:: Foldable f
=> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> G3PSeed
-> G3PKey
g3pKey_fromSeed :: forall (f :: * -> *).
Foldable f =>
HmacKey
-> f ByteString -> ByteString -> ByteString -> G3PSeed -> G3PKey
g3pKey_fromSeed HmacKey
key f ByteString
role ByteString
tag ByteString
ekey G3PSeed
seed =
G3PSeed
-> HmacKey -> f ByteString -> ByteString -> ByteString -> G3PKey
forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey -> f ByteString -> ByteString -> ByteString -> G3PKey
g3pSeed_toKey G3PSeed
seed HmacKey
key f ByteString
role ByteString
tag ByteString
ekey
g3pKey_fromSprout
:: Foldable f
=> f ByteString
-> ByteString
-> ByteString
-> G3PSprout
-> G3PKey
g3pKey_fromSprout :: forall (f :: * -> *).
Foldable f =>
f ByteString -> ByteString -> ByteString -> G3PSprout -> G3PKey
g3pKey_fromSprout f ByteString
role ByteString
tag ByteString
key G3PSprout
sprout =
G3PSprout -> f ByteString -> ByteString -> ByteString -> G3PKey
forall (f :: * -> *).
Foldable f =>
G3PSprout -> f ByteString -> ByteString -> ByteString -> G3PKey
g3pSprout_toKey G3PSprout
sprout f ByteString
role ByteString
tag ByteString
key
g3pKey_fromTree
:: ByteString
-> G3PTree
-> G3PKey
g3pKey_fromTree :: ByteString -> G3PTree -> G3PKey
g3pKey_fromTree = (G3PTree -> ByteString -> G3PKey)
-> ByteString -> G3PTree -> G3PKey
forall a b c. (a -> b -> c) -> b -> a -> c
flip G3PTree -> ByteString -> G3PKey
g3pTree_toKey
g3pSource
:: Foldable f
=> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSource :: forall (f :: * -> *).
Foldable f =>
G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSource = (G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall a b. (a -> b) -> (G3PInputs -> a) -> G3PInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSpark_toSource ((G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSalt -> G3PInputs -> G3PSpark
g3pSpark
g3pSource_fromSpark
:: Foldable f
=> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSpark -> G3PSource
g3pSource_fromSpark :: forall (f :: * -> *).
Foldable f =>
G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSpark
-> G3PSource
g3pSource_fromSpark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag G3PSpark
spark =
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSpark_toSource G3PSpark
spark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag
g3pSource_fromSeed
:: Foldable f
=> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSeed
-> G3PSource
g3pSource_fromSeed :: forall (f :: * -> *).
Foldable f =>
HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSeed
-> G3PSource
g3pSource_fromSeed HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag G3PSeed
seed =
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSeed_toSource G3PSeed
seed HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag
g3pSource_fromSprout
:: Foldable f
=> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSprout
-> G3PSource
g3pSource_fromSprout :: forall (f :: * -> *).
Foldable f =>
f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSprout
-> G3PSource
g3pSource_fromSprout f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag G3PSprout
sprout =
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
forall (f :: * -> *).
Foldable f =>
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSource
g3pSprout_toSource G3PSprout
sprout f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag
g3pSource_fromTree
:: ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PTree
-> G3PSource
g3pSource_fromTree :: ByteString
-> ByteString -> Word32 -> ByteString -> G3PTree -> G3PSource
g3pSource_fromTree ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag G3PTree
tree =
G3PTree
-> ByteString -> ByteString -> Word32 -> ByteString -> G3PSource
g3pTree_toSource G3PTree
tree ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag
g3pSource_fromKey
:: ByteString
-> Word32
-> ByteString
-> G3PKey
-> G3PSource
g3pSource_fromKey :: ByteString -> Word32 -> ByteString -> G3PKey -> G3PSource
g3pSource_fromKey ByteString
ehdr Word32
ectr ByteString
etag G3PKey
key =
G3PKey -> ByteString -> Word32 -> ByteString -> G3PSource
g3pKey_toSource G3PKey
key ByteString
ehdr Word32
ectr ByteString
etag
g3pStream
:: Foldable f
=> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pStream :: forall (f :: * -> *).
Foldable f =>
G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pStream = (G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall a b. (a -> b) -> (G3PInputs -> a) -> G3PInputs -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSpark_toStream ((G3PInputs -> G3PSpark)
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString)
-> (G3PSalt -> G3PInputs -> G3PSpark)
-> G3PSalt
-> G3PInputs
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. G3PSalt -> G3PInputs -> G3PSpark
g3pSpark
g3pStream_fromSpark
:: Foldable f
=> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSpark -> Stream ByteString
g3pStream_fromSpark :: forall (f :: * -> *).
Foldable f =>
G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSpark
-> Stream ByteString
g3pStream_fromSpark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag G3PSpark
spark =
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall (f :: * -> *).
Foldable f =>
G3PSpark
-> G3PSeedInputs
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSpark_toStream G3PSpark
spark G3PSeedInputs
inputs HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag
g3pStream_fromSeed
:: Foldable f
=> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSeed
-> Stream ByteString
g3pStream_fromSeed :: forall (f :: * -> *).
Foldable f =>
HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSeed
-> Stream ByteString
g3pStream_fromSeed HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag G3PSeed
seed =
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall (f :: * -> *).
Foldable f =>
G3PSeed
-> HmacKey
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSeed_toStream G3PSeed
seed HmacKey
key f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag
g3pStream_fromSprout
:: Foldable f
=> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSprout -> Stream ByteString
g3pStream_fromSprout :: forall (f :: * -> *).
Foldable f =>
f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PSprout
-> Stream ByteString
g3pStream_fromSprout f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag G3PSprout
sprout =
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
forall (f :: * -> *).
Foldable f =>
G3PSprout
-> f ByteString
-> ByteString
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pSprout_toStream G3PSprout
sprout f ByteString
role ByteString
tag ByteString
ekey ByteString
ehdr Word32
ectr ByteString
etag
g3pStream_fromTree
:: ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PTree -> Stream ByteString
g3pStream_fromTree :: ByteString
-> ByteString
-> Word32
-> ByteString
-> G3PTree
-> Stream ByteString
g3pStream_fromTree ByteString
key ByteString
hdr Word32
ctr ByteString
tag G3PTree
tree =
G3PTree
-> ByteString
-> ByteString
-> Word32
-> ByteString
-> Stream ByteString
g3pTree_toStream G3PTree
tree ByteString
key ByteString
hdr Word32
ctr ByteString
tag
g3pStream_fromKey
:: ByteString
-> Word32
-> ByteString
-> G3PKey -> Stream ByteString
g3pStream_fromKey :: ByteString -> Word32 -> ByteString -> G3PKey -> Stream ByteString
g3pStream_fromKey ByteString
hdr Word32
ctr ByteString
tag G3PKey
key =
G3PKey -> ByteString -> Word32 -> ByteString -> Stream ByteString
g3pKey_toStream G3PKey
key ByteString
hdr Word32
ctr ByteString
tag
g3pStream_fromSource :: G3PSource -> Stream ByteString
g3pStream_fromSource :: G3PSource -> Stream ByteString
g3pStream_fromSource = G3PSource -> Stream ByteString
g3pSource_toStream