{-# LANGUAGE OverloadedStrings #-} ------------------------------------------------------------------------------- -- | -- Module: Crypto.G3P.V2.Foxtrot -- Copyright: (c) 2024 Auth Global -- License: Apache2 -- ------------------------------------------------------------------------------- {- | Stripped-down version of G3Pb2 charlie, primarily intended for server-side application. This uses HMAC-SHA256 both to generate inputs to bcrypt and to summarize the resulting bcrypt state. Assuming your deployment is basically a traditional give-me-your-password authentication protocol but with prehashing, I recommend a two-step approach to counteracting prehash precomputation attacks. First, I recommend that the server apply at least as much key-stretching as the client. Second, I recommend this server-side key-stretching be protected by a secret HMAC key. In such a deployment, a cracker could front-load half of the computation needed to guess a password at significant storage expense. This is far less appealing to the cracker than being able to front-load nearly all of the computation needed while incurring the same expense to store the intermediate guesses. The test suite's MyCorpExample.hs contains an example of how one might use these functions in a deployment. By using reduced-round calls to 'g3pFoxtrot' in conjuction with argon2, one can make precomputation an even less appealing strategy, as the key-stretching occurs server-side is significantly more expensive than the prehash itself. -} module Crypto.G3P.V2.Foxtrot where import Data.ByteString (ByteString) import qualified Data.ByteString as B import Data.Function((&)) import Data.Word import Data.Vector(Vector) import qualified Data.Vector as V import Crypto.G3P.BCrypt (bcryptXsFree) import Crypto.PHKDF import Crypto.Encoding.PHKDF (takeBs, nullBuffer) import Network.ByteOrder(bytestring64) data G3PFoxtrotSalt = G3PFoxtrotSalt { g3pFoxtrotSalt_key :: !HmacKey , g3pFoxtrotSalt_longTag :: !ByteString , g3pFoxtrotSalt_contextTags :: !(Vector ByteString) , g3pFoxtrotSalt_domainTag :: !ByteString , g3pFoxtrotSalt_bcryptRounds :: !Word32 } -- | G3Pb2 foxtrot is a function that incorporates a bcrypt-like key-stretching -- phase. Stripped down version of G3Pb2 charlie, without a built-in continuation -- control key. @test/MyCorpExample.hs@ uses this as a server-side cryptoacoustic -- component that sandwiches the comparatively silent argon2. g3pFoxtrot :: (Foldable f, Foldable g) => G3PFoxtrotSalt -> f ByteString -> g ByteString -> Word32 -> ByteString g3pFoxtrot salt inputs = doTweak where foxtrot = "G3Pb2 foxtrot" key = g3pFoxtrotSalt_key salt longTag = g3pFoxtrotSalt_longTag salt contextTags = g3pFoxtrotSalt_contextTags salt domainTag = g3pFoxtrotSalt_domainTag salt rounds = g3pFoxtrotSalt_bcryptRounds salt spark = phkdfCtx_init key & phkdfCtx_feedArg foxtrot & phkdfCtx_feedArgs inputs & phkdfCtx_toHmacKeyPrefixed (B.concat . flip takeBs [domainTag, "\x00", longTag, nullBuffer] . fromIntegral) -- G3Pb2 foxtrot doesn't ever explicitly encode the length of the syntax -- generated by bcryptXsFree in the plaintext of the HMAC message itself. -- This length of this syntax is determined by the number of superrounds, -- which in turn is determined by the number of bcrypt rounds. -- This doesn't create any homophones, a.k.a. "canonicalization attacks", -- which is terminology that the algebraist in me isn't fond of. -- It can't cause homophones because the number of rounds, and thus this -- syntax length, is encoded in the bcrypt key-stretching phase well before -- the very first bcrypt output byte is generated. As these bytes are -- then consumed by HMAC, their overall length is implicitly encoded into -- the HMAC message. -- Not to mention that there are heurstic methods to parse the generated -- HMAC syntax without knowing the number of bcrypt rounds up front -- that will perform with perfect accuracy on most or all actual -- deployments. Every superround results in a fixed-length, multi-kilobyte -- syntax string appended to the message, which is much much longer than -- the expected length of the remaining parameters. Futhermore each -- multi-kilobyte superround syntax string always contains the literal -- sequence of bytes "OrpheanBeholderScryDoubt" in a fixed location, -- which in practice won't appear in other parameters. bcryptName = B.concat [ "G3Pb2 bcrypt-xs-free" , bytestring64 (8 * fromIntegral (B.length longTag)) ] (_tagPos, seed) = bcryptXsFree id bcryptName V.empty longTag contextTags domainTag rounds spark sprout = phkdfCtx_initPrefixed (B.concat $ takeBs 32 [domainTag, "\x00", foxtrot, nullBuffer]) seed & phkdfCtx_feedArgs contextTags doTweak tweak counter = phkdfCtx_feedArgs tweak sprout & phkdfCtx_finalize (B.concat . flip takeBs (cycle [domainTag, "\x00"]) . fromIntegral) counter domainTag -- | G3Pb2 tango: a simple application of PHKDF used to derive secret server-side -- salts in @test/MyCorpExample.hs@. -- TODO: rewrite this in a more point-free style, in order to better support partial application g3pTango :: (Foldable f) => HmacKey -> f ByteString -- ^ inputs -> Word32 -- ^ counter -> ByteString -- ^ domain tag -> ByteString -- ^ 32-byte output hash g3pTango key inputs counter domainTag = out where tango = "G3Pb2 tango" out = phkdfCtx_init key & phkdfCtx_feedArg tango & phkdfCtx_feedArgs inputs & phkdfCtx_finalize (B.concat . flip takeBs (cycle [domainTag, "\x00"]) . fromIntegral) counter domainTag