Add XSalsa.derive and example

This function adds one more HSalsa key derivation to an XSalsa context
that has previously been initialized.  It allows multi-level cascades
like the 2-level done by NaCl crypto_box.
This commit is contained in:
Olivier Chéron 2019-08-31 09:10:46 +02:00
parent 65643a3bea
commit 096e2ec0bd
4 changed files with 93 additions and 5 deletions

View File

@ -12,6 +12,7 @@
{-# LANGUAGE ForeignFunctionInterface #-}
module Crypto.Cipher.XSalsa
( initialize
, derive
, combine
, generate
, State
@ -44,5 +45,31 @@ initialize nbRounds key nonce
where kLen = B.length key
nonceLen = B.length nonce
-- | Use an already initialized context and new nonce material to derive another
-- XSalsa context.
--
-- This allows a multi-level cascade where a first key @k1@ and nonce @n1@ is
-- used to get @HState(k1,n1)@, and this value is then used as key @k2@ to build
-- @XSalsa(k2,n2)@. Function 'initialize' is to be called with the first 192
-- bits of @n1|n2@, and the call to @derive@ should add the remaining 128 bits.
--
-- The output context always uses the same number of rounds as the input
-- context.
derive :: ByteArrayAccess nonce
=> State -- ^ base XSalsa state
-> nonce -- ^ the remainder nonce (128 bits)
-> State -- ^ the new XSalsa state
derive (State stPtr') nonce
| nonceLen /= 16 = error "XSalsa: nonce length should be 128 bits"
| otherwise = unsafeDoIO $ do
stPtr <- B.copy stPtr' $ \stPtr ->
B.withByteArray nonce $ \noncePtr ->
ccryptonite_xsalsa_derive stPtr nonceLen noncePtr
return $ State stPtr
where nonceLen = B.length nonce
foreign import ccall "cryptonite_xsalsa_init"
ccryptonite_xsalsa_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()
foreign import ccall "cryptonite_xsalsa_derive"
ccryptonite_xsalsa_derive :: Ptr State -> Int -> Ptr Word8 -> IO ()

View File

@ -8,6 +8,9 @@ module Crypto.Tutorial
-- * Symmetric block ciphers
-- $symmetric_block_ciphers
-- * Combining primitives
-- $combining_primitives
) where
-- $api_design
@ -147,3 +150,46 @@ module Crypto.Tutorial
-- > putStrLn $ "Original Message: " ++ show msg
-- > putStrLn $ "Message after encryption: " ++ show eMsg
-- > putStrLn $ "Message after decryption: " ++ show dMsg
-- $combining_primitives
--
-- This example shows how to use Curve25519, XSalsa and Poly1305 primitives to
-- emulate NaCl's @crypto_box@ construct.
--
-- > import qualified Data.ByteArray as BA
-- > import Data.ByteString (ByteString)
-- > import qualified Data.ByteString as B
-- >
-- > import qualified Crypto.Cipher.XSalsa as XSalsa
-- > import qualified Crypto.MAC.Poly1305 as Poly1305
-- > import qualified Crypto.PubKey.Curve25519 as X25519
-- >
-- > -- | Build a @crypto_box@ packet encrypting the specified content with a
-- > -- 192-bit nonce, receiver public key and sender private key.
-- > crypto_box content nonce pk sk = BA.convert tag `B.append` c
-- > where
-- > zero = B.replicate 16 0
-- > shared = X25519.dh pk sk
-- > (iv0, iv1) = B.splitAt 8 nonce
-- > state0 = XSalsa.initialize 20 shared (zero `B.append` iv0)
-- > state1 = XSalsa.derive state0 iv1
-- > (rs, state2) = XSalsa.generate state1 32
-- > (c, _) = XSalsa.combine state2 content
-- > tag = Poly1305.auth (rs :: ByteString) c
-- >
-- > -- | Try to open a @crypto_box@ packet and recover the content using the
-- > -- 192-bit nonce, sender public key and receiver private key.
-- > crypto_box_open packet nonce pk sk
-- > | B.length packet < 16 = Nothing
-- > | BA.constEq tag' tag = Just content
-- > | otherwise = Nothing
-- > where
-- > (tag', c) = B.splitAt 16 packet
-- > zero = B.replicate 16 0
-- > shared = X25519.dh pk sk
-- > (iv0, iv1) = B.splitAt 8 nonce
-- > state0 = XSalsa.initialize 20 shared (zero `B.append` iv0)
-- > state1 = XSalsa.derive state0 iv1
-- > (rs, state2) = XSalsa.generate state1 32
-- > (content, _) = XSalsa.combine state2 c
-- > tag = Poly1305.auth (rs :: ByteString) c

View File

@ -47,13 +47,27 @@ void cryptonite_xsalsa_init(cryptonite_salsa_context *ctx, uint8_t nb_rounds,
(x6, x7, x8, x9) is the first 128 bits of a 192-bit nonce
*/
cryptonite_salsa_init_core(&ctx->st, keylen, key, 8, iv);
ctx->st.d[ 8] = load_le32(iv + 8);
ctx->st.d[ 9] = load_le32(iv + 12);
/* Continue initialization in a separate function that may also
be called independently */
cryptonite_xsalsa_derive(ctx, ivlen - 8, iv + 8);
}
void cryptonite_xsalsa_derive(cryptonite_salsa_context *ctx,
uint32_t ivlen, const uint8_t *iv)
{
/* Finish creating initial 512-bit input block:
(x6, x7, x8, x9) is the first 128 bits of a 192-bit nonce
Except iv has been shifted by 64 bits so there are now only 128 bits ahead.
*/
ctx->st.d[ 8] += load_le32(iv + 0);
ctx->st.d[ 9] += load_le32(iv + 4);
/* Compute (z0, z1, . . . , z15) = doubleround ^(r/2) (x0, x1, . . . , x15) */
block hSalsa;
memset(&hSalsa, 0, sizeof(block));
cryptonite_salsa_core_xor(nb_rounds, &hSalsa, &ctx->st);
cryptonite_salsa_core_xor(ctx->nb_rounds, &hSalsa, &ctx->st);
/* Build a new 512-bit input block (x0, x1, . . . , x15):
(x0, x5, x10, x15) is the Salsa20 constant
@ -69,8 +83,8 @@ void cryptonite_xsalsa_init(cryptonite_salsa_context *ctx, uint8_t nb_rounds,
ctx->st.d[12] = hSalsa.d[ 7] - ctx->st.d[ 7];
ctx->st.d[13] = hSalsa.d[ 8] - ctx->st.d[ 8];
ctx->st.d[14] = hSalsa.d[ 9] - ctx->st.d[ 9];
ctx->st.d[ 6] = load_le32(iv + 16);
ctx->st.d[ 7] = load_le32(iv + 20);
ctx->st.d[ 6] = load_le32(iv + 8);
ctx->st.d[ 7] = load_le32(iv + 12);
ctx->st.d[ 8] = 0;
ctx->st.d[ 9] = 0;
}

View File

@ -33,5 +33,6 @@
#include "cryptonite_salsa.h"
void cryptonite_xsalsa_init(cryptonite_salsa_context *ctx, uint8_t nb_rounds, uint32_t keylen, const uint8_t *key, uint32_t ivlen, const uint8_t *iv);
void cryptonite_xsalsa_derive(cryptonite_salsa_context *ctx, uint32_t ivlen, const uint8_t *iv);
#endif