Skip to content

Commit

Permalink
Merge PR #18
Browse files Browse the repository at this point in the history
  • Loading branch information
kazu-yamamoto committed Sep 25, 2023
2 parents b46ec56 + df25896 commit 54bc6df
Show file tree
Hide file tree
Showing 6 changed files with 192 additions and 7 deletions.
26 changes: 26 additions & 0 deletions Crypto/Cipher/ChaCha.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Cipher.ChaCha
( initialize
, initializeX
, combine
, generate
, State
Expand Down Expand Up @@ -53,6 +54,28 @@ initialize nbRounds key nonce
where kLen = B.length key
nonceLen = B.length nonce

-- | Initialize a new XChaCha context with the number of rounds,
-- the key and the nonce associated.
--
-- An XChaCha state can be used like a regular ChaCha state after initialisation.
initializeX :: (ByteArrayAccess key, ByteArrayAccess nonce)
=> Int -- ^ number of rounds (8,12,20)
-> key -- ^ the key (256 bits)
-> nonce -- ^ the nonce (192 bits)
-> State -- ^ the initial ChaCha state
initializeX nbRounds key nonce
| kLen /= 32 = error "XChaCha: key length should be 256 bits"
| nonceLen /= 24 = error "XChaCha: nonce length should be 192 bits"
| nbRounds `notElem` [8,12,20] = error "XChaCha: rounds should be 8, 12 or 20"
| otherwise = unsafeDoIO $ do
stPtr <- B.alloc 132 $ \stPtr ->
B.withByteArray nonce $ \noncePtr ->
B.withByteArray key $ \keyPtr ->
ccrypton_xchacha_init stPtr nbRounds keyPtr noncePtr
return $ State stPtr
where kLen = B.length key
nonceLen = B.length nonce

-- | Initialize simple ChaCha State
--
-- The seed need to be at least 40 bytes long
Expand Down Expand Up @@ -115,6 +138,9 @@ foreign import ccall "crypton_chacha_init_core"
foreign import ccall "crypton_chacha_init"
ccrypton_chacha_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()

foreign import ccall "crypton_xchacha_init"
ccrypton_xchacha_init :: Ptr State -> Int -> Ptr Word8 -> Ptr Word8 -> IO ()

foreign import ccall "crypton_chacha_combine"
ccrypton_chacha_combine :: Ptr Word8 -> Ptr State -> Ptr Word8 -> CUInt -> IO ()

Expand Down
40 changes: 38 additions & 2 deletions Crypto/Cipher/ChaChaPoly1305.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,10 +38,13 @@
module Crypto.Cipher.ChaChaPoly1305
( State
, Nonce
, XNonce
, nonce12
, nonce8
, nonce24
, incrementNonce
, initialize
, initializeX
, appendAAD
, finalizeAAD
, encrypt
Expand Down Expand Up @@ -81,6 +84,14 @@ instance ByteArrayAccess Nonce where
withByteArray (Nonce8 n) = B.withByteArray n
withByteArray (Nonce12 n) = B.withByteArray n

-- | Extended nonce for XChaChaPoly1305.
newtype XNonce = Nonce24 Bytes

instance ByteArrayAccess XNonce where
length (Nonce24 n) = B.length n
withByteArray (Nonce24 n) = B.withByteArray n


-- Based on the following pseudo code:
--
-- chacha20_aead_encrypt(aad, key, iv, constant, plaintext):
Expand Down Expand Up @@ -117,6 +128,13 @@ nonce8 constant iv
| B.length iv /= 8 = CryptoFailed CryptoError_IvSizeInvalid
| otherwise = CryptoPassed . Nonce8 . B.concat $ [constant, iv]

-- | 24 bytes IV, extended nonce constructor
nonce24 :: ByteArrayAccess ba
=> ba -> CryptoFailable XNonce
nonce24 iv
| B.length iv /= 24 = CryptoFailed CryptoError_IvSizeInvalid
| otherwise = CryptoPassed . Nonce24 . B.convert $ iv

-- | Increment a nonce
incrementNonce :: Nonce -> Nonce
incrementNonce (Nonce8 n) = Nonce8 $ incrementNonce' n 4
Expand All @@ -143,16 +161,34 @@ initialize :: ByteArrayAccess key
initialize key (Nonce8 nonce) = initialize' key nonce
initialize key (Nonce12 nonce) = initialize' key nonce


initialize' :: ByteArrayAccess key
=> key -> Bytes -> CryptoFailable State
initialize' key nonce
| B.length key /= 32 = CryptoFailed CryptoError_KeySizeInvalid
| otherwise = CryptoPassed $ State encState polyState 0 0
| otherwise = CryptoPassed $ initFromRootState rootState
where rootState = ChaCha.initialize 20 key nonce


initFromRootState :: ChaCha.State -> State
initFromRootState rootState = State encState polyState 0 0
where
rootState = ChaCha.initialize 20 key nonce
(polyKey, encState) = ChaCha.generate rootState 64
polyState = throwCryptoError $ Poly1305.initialize (B.take 32 polyKey :: ScrubbedBytes)


-- | Initialize a new XChaChaPoly1305 State
--
-- The key length needs to be 256 bits, and the nonce
-- procured using `nonce24`.
initializeX :: ByteArrayAccess key
=> key -> XNonce -> CryptoFailable State
initializeX key (Nonce24 nonce)
| B.length key /= 32 = CryptoFailed CryptoError_KeySizeInvalid
| otherwise = CryptoPassed $ initFromRootState rootState
where rootState = ChaCha.initializeX 20 key nonce


-- | Append Authenticated Data to the State and return
-- the new modified State.
--
Expand Down
95 changes: 91 additions & 4 deletions cbits/crypton_chacha.c
Original file line number Diff line number Diff line change
Expand Up @@ -92,10 +92,43 @@ static void chacha_core(int rounds, block *out, const crypton_chacha_state *in)
out->d[15] = cpu_to_le32(x15);
}

/* only 2 valids values are 256 (32) and 128 (16) */
void crypton_chacha_init_core(crypton_chacha_state *st,
uint32_t keylen, const uint8_t *key,
uint32_t ivlen, const uint8_t *iv)
static void hchacha_core(int rounds, uint32_t *out, const crypton_chacha_state *in)
{
uint32_t x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15;
int i;

x0 = in->d[0]; x1 = in->d[1]; x2 = in->d[2]; x3 = in->d[3];
x4 = in->d[4]; x5 = in->d[5]; x6 = in->d[6]; x7 = in->d[7];
x8 = in->d[8]; x9 = in->d[9]; x10 = in->d[10]; x11 = in->d[11];
x12 = in->d[12]; x13 = in->d[13]; x14 = in->d[14]; x15 = in->d[15];

for (i = rounds; i > 0; i -= 2) {
QR(x0, x4, x8, x12);
QR(x1, x5, x9, x13);
QR(x2, x6, x10, x14);
QR(x3, x7, x11, x15);

QR(x0, x5, x10, x15);
QR(x1, x6, x11, x12);
QR(x2, x7, x8, x13);
QR(x3, x4, x9, x14);
}

/* HChaCha doesn't perform the final addition */

out[0] = cpu_to_le32(x0);
out[1] = cpu_to_le32(x1);
out[2] = cpu_to_le32(x2);
out[3] = cpu_to_le32(x3);
out[4] = cpu_to_le32(x12);
out[5] = cpu_to_le32(x13);
out[6] = cpu_to_le32(x14);
out[7] = cpu_to_le32(x15);
}

/* Common initialization logic for ChaCha20 and HChaCha20 */
static void chacha_init_key_state(crypton_chacha_state *st,
uint32_t keylen, const uint8_t *key)
{
const uint8_t *constants = (keylen == 32) ? sigma : tau;

Expand All @@ -117,6 +150,14 @@ void crypton_chacha_init_core(crypton_chacha_state *st,
st->d[9] = load_le32(key + 4);
st->d[10] = load_le32(key + 8);
st->d[11] = load_le32(key + 12);
}

/* only 2 valids values are 256 (32) and 128 (16) */
void crypton_chacha_init_core(crypton_chacha_state *st,
uint32_t keylen, const uint8_t *key,
uint32_t ivlen, const uint8_t *iv)
{
chacha_init_key_state(st, keylen, key);
st->d[12] = 0;
switch (ivlen) {
case 8:
Expand All @@ -133,6 +174,19 @@ void crypton_chacha_init_core(crypton_chacha_state *st,
}
}

void crypton_hchacha_init_core(crypton_chacha_state *st,
const uint8_t *key,
const uint8_t *iv)
{
/* keylen is always 32 here */
chacha_init_key_state(st, 32, key);
/* fill the last 4 uint32s with the 128-bit nonce */
st->d[12] = load_le32(iv + 0);
st->d[13] = load_le32(iv + 4);
st->d[14] = load_le32(iv + 8);
st->d[15] = load_le32(iv + 12);
}

void crypton_chacha_init(crypton_chacha_context *ctx, uint8_t nb_rounds,
uint32_t keylen, const uint8_t *key,
uint32_t ivlen, const uint8_t *iv)
Expand All @@ -142,6 +196,39 @@ void crypton_chacha_init(crypton_chacha_context *ctx, uint8_t nb_rounds,
crypton_chacha_init_core(&ctx->st, keylen, key, ivlen, iv);
}

void crypton_hchacha(uint8_t nb_rounds, const uint8_t *keyin, const uint8_t *iv,
uint8_t *keyout)
{
crypton_chacha_state st;

crypton_hchacha_init_core(&st, keyin, iv);
/* output to uint32_t* and do a memcpy to avoid
violating the strict aliasing rule */
uint32_t keyout32[8];
hchacha_core(nb_rounds, keyout32, &st);
memset(&st, 0, sizeof(st));
memcpy(keyout, keyout32, 32);

memset(keyout32, 0, 32);
}

/* XChaCha: 256-bit key, 192-bit nonce version of ChaCha.*/
void crypton_xchacha_init(crypton_chacha_context *ctx, uint8_t nb_rounds,
const uint8_t *key, const uint8_t *iv)
{
memset(ctx, 0, sizeof(*ctx));
ctx->nb_rounds = nb_rounds;

/* perform HChaCha with the key and the first 16 bytes of the nonce
to get the subkey */
uint8_t subkey[32];
crypton_hchacha(nb_rounds, key, iv, subkey);
/* perform regular ChaCha with the generated subkey and the last 8 bytes
of the input IV */
crypton_chacha_init_core(&ctx->st, 32, subkey, 8, iv + 16);
}


void crypton_chacha_combine(uint8_t *dst, crypton_chacha_context *ctx, const uint8_t *src, uint32_t bytes)
{
block out;
Expand Down
1 change: 1 addition & 0 deletions cbits/crypton_chacha.h
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ typedef struct {

void crypton_chacha_init_core(crypton_chacha_state *st, uint32_t keylen, const uint8_t *key, uint32_t ivlen, const uint8_t *iv);
void crypton_chacha_init(crypton_chacha_context *ctx, uint8_t nb_rounds, uint32_t keylen, const uint8_t *key, uint32_t ivlen, const uint8_t *iv);
void crypton_xchacha_init(crypton_chacha_context *ctx, uint8_t nb_rounds, const uint8_t *key, const uint8_t *iv);
void crypton_chacha_combine(uint8_t *dst, crypton_chacha_context *st, const uint8_t *src, uint32_t bytes);
void crypton_chacha_generate(uint8_t *dst, crypton_chacha_context *st, uint32_t bytes);

Expand Down
13 changes: 13 additions & 0 deletions tests/ChaCha.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,18 @@ b12_256_k0_i0 =
b20_256_k0_i0 =
"\x76\xb8\xe0\xad\xa0\xf1\x3d\x90\x40\x5d\x6a\xe5\x53\x86\xbd\x28\xbd\xd2\x19\xb8\xa0\x8d\xed\x1a\xa8\x36\xef\xcc\x8b\x77\x0d\xc7\xda\x41\x59\x7c\x51\x57\x48\x8d\x77\x24\xe0\x3f\xb8\xd8\x4a\x37\x6a\x43\xb8\xf4\x15\x18\xa1\x1c\xc3\x87\xb6\x69\xb2\xee\x65\x86\x9f\x07\xe7\xbe\x55\x51\x38\x7a\x98\xba\x97\x7c\x73\x2d\x08\x0d\xcb\x0f\x29\xa0\x48\xe3\x65\x69\x12\xc6\x53\x3e\x32\xee\x7a\xed\x29\xb7\x21\x76\x9c\xe6\x4e\x43\xd5\x71\x33\xb0\x74\xd8\x39\xd5\x31\xed\x1f\x28\x51\x0a\xfb\x45\xac\xe1\x0a\x1f\x4b\x79\x4d\x6f"

-- XChaCha20 test vector from RFC draft: https://datatracker.ietf.org/doc/html/draft-arciszewski-xchacha

xChaCha20_ExampleKAT = expected @=? fst (ChaCha.combine initState plaintext)
where iv = B.pack $ [0x40 .. 0x56] ++ [0x58]
key = B.pack [0x80 .. 0x9f]
initState = ChaCha.initializeX 20 key iv
plaintext :: B.ByteString
plaintext = "The dhole (pronounced \"dole\") is also known as the Asiatic wild dog, red dog, and whistling dog. It is about the size of a German shepherd but looks more like a long-legged fox. This highly elusive and skilled jumper is classified with wolves, coyotes, jackals, and foxes in the taxonomic family Canidae."
expected :: B.ByteString
expected = "\x45\x59\xab\xba\x4e\x48\xc1\x61\x02\xe8\xbb\x2c\x05\xe6\x94\x7f\x50\xa7\x86\xde\x16\x2f\x9b\x0b\x7e\x59\x2a\x9b\x53\xd0\xd4\xe9\x8d\x8d\x64\x10\xd5\x40\xa1\xa6\x37\x5b\x26\xd8\x0d\xac\xe4\xfa\xb5\x23\x84\xc7\x31\xac\xbf\x16\xa5\x92\x3c\x0c\x48\xd3\x57\x5d\x4d\x0d\x2c\x67\x3b\x66\x6f\xaa\x73\x10\x61\x27\x77\x01\x09\x3a\x6b\xf7\xa1\x58\xa8\x86\x42\x92\xa4\x1c\x48\xe3\xa9\xb4\xc0\xda\xec\xe0\xf8\xd9\x8d\x0d\x7e\x05\xb3\x7a\x30\x7b\xbb\x66\x33\x31\x64\xec\x9e\x1b\x24\xea\x0d\x6c\x3f\xfd\xdc\xec\x4f\x68\xe7\x44\x30\x56\x19\x3a\x03\xc8\x10\xe1\x13\x44\xca\x06\xd8\xed\x8a\x2b\xfb\x1e\x8d\x48\xcf\xa6\xbc\x0e\xb4\xe2\x46\x4b\x74\x81\x42\x40\x7c\x9f\x43\x1a\xee\x76\x99\x60\xe1\x5b\xa8\xb9\x68\x90\x46\x6e\xf2\x45\x75\x99\x85\x23\x85\xc6\x61\xf7\x52\xce\x20\xf9\xda\x0c\x09\xab\x6b\x19\xdf\x74\xe7\x6a\x95\x96\x74\x46\xf8\xd0\xfd\x41\x5e\x7b\xee\x2a\x12\xa1\x14\xc2\x0e\xb5\x29\x2a\xe7\xa3\x49\xae\x57\x78\x20\xd5\x52\x0a\x1f\x3f\xb6\x2a\x17\xce\x6a\x7e\x68\xfa\x7c\x79\x11\x1d\x88\x60\x92\x0b\xc0\x48\xef\x43\xfe\x84\x48\x6c\xcb\x87\xc2\x5f\x0a\xe0\x45\xf0\xcc\xe1\xe7\x98\x9a\x9a\xa2\x20\xa2\x8b\xdd\x48\x27\xe7\x51\xa2\x4a\x6d\x5c\x62\xd7\x90\xa6\x63\x93\xb9\x31\x11\xc1\xa5\x5d\xd7\x42\x1a\x10\x18\x49\x74\xc7\xc5"


data Vector = Vector Int -- rounds
ByteString -- key
ByteString -- nonce
Expand All @@ -38,6 +50,7 @@ tests = testGroup "ChaCha"
, testCase "8-256-K0-I0" (chachaRunSimple b8_256_k0_i0 8 32 8)
, testCase "12-256-K0-I0" (chachaRunSimple b12_256_k0_i0 12 32 8)
, testCase "20-256-K0-I0" (chachaRunSimple b20_256_k0_i0 20 32 8)
, testCase "XChaCha20 example KAT" xChaCha20_ExampleKAT
, testProperty "generate-combine" chachaGenerateCombine
, testProperty "chunking-generate" chachaGenerateChunks
, testProperty "chunking-combine" chachaCombineChunks
Expand Down
24 changes: 23 additions & 1 deletion tests/ChaChaPoly1305.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,14 +9,17 @@ import Poly1305 ()
import qualified Data.ByteString as B
import qualified Data.ByteArray as B (convert)

plaintext, aad, key, iv, ciphertext, tag, nonce1, nonce2, nonce3, nonce4, nonce5, nonce6, nonce7, nonce8, nonce9, nonce10 :: B.ByteString
plaintext, aad, key, iv, ivX, ciphertext, ciphertextX, tag, tagX, nonce1, nonce2, nonce3, nonce4, nonce5, nonce6, nonce7, nonce8, nonce9, nonce10 :: B.ByteString
plaintext = "Ladies and Gentlemen of the class of '99: If I could offer you only one tip for the future, sunscreen would be it."
aad = "\x50\x51\x52\x53\xc0\xc1\xc2\xc3\xc4\xc5\xc6\xc7"
key = "\x80\x81\x82\x83\x84\x85\x86\x87\x88\x89\x8a\x8b\x8c\x8d\x8e\x8f\x90\x91\x92\x93\x94\x95\x96\x97\x98\x99\x9a\x9b\x9c\x9d\x9e\x9f"
iv = "\x40\x41\x42\x43\x44\x45\x46\x47"
ivX = B.pack [0x40 .. 0x57]
constant = "\x07\x00\x00\x00"
ciphertext = "\xd3\x1a\x8d\x34\x64\x8e\x60\xdb\x7b\x86\xaf\xbc\x53\xef\x7e\xc2\xa4\xad\xed\x51\x29\x6e\x08\xfe\xa9\xe2\xb5\xa7\x36\xee\x62\xd6\x3d\xbe\xa4\x5e\x8c\xa9\x67\x12\x82\xfa\xfb\x69\xda\x92\x72\x8b\x1a\x71\xde\x0a\x9e\x06\x0b\x29\x05\xd6\xa5\xb6\x7e\xcd\x3b\x36\x92\xdd\xbd\x7f\x2d\x77\x8b\x8c\x98\x03\xae\xe3\x28\x09\x1b\x58\xfa\xb3\x24\xe4\xfa\xd6\x75\x94\x55\x85\x80\x8b\x48\x31\xd7\xbc\x3f\xf4\xde\xf0\x8e\x4b\x7a\x9d\xe5\x76\xd2\x65\x86\xce\xc6\x4b\x61\x16"
ciphertextX = "\xbd\x6d\x17\x9d\x3e\x83\xd4\x3b\x95\x76\x57\x94\x93\xc0\xe9\x39\x57\x2a\x17\x00\x25\x2b\xfa\xcc\xbe\xd2\x90\x2c\x21\x39\x6c\xbb\x73\x1c\x7f\x1b\x0b\x4a\xa6\x44\x0b\xf3\xa8\x2f\x4e\xda\x7e\x39\xae\x64\xc6\x70\x8c\x54\xc2\x16\xcb\x96\xb7\x2e\x12\x13\xb4\x52\x2f\x8c\x9b\xa4\x0d\xb5\xd9\x45\xb1\x1b\x69\xb9\x82\xc1\xbb\x9e\x3f\x3f\xac\x2b\xc3\x69\x48\x8f\x76\xb2\x38\x35\x65\xd3\xff\xf9\x21\xf9\x66\x4c\x97\x63\x7d\xa9\x76\x88\x12\xf6\x15\xc6\x8b\x13\xb5\x2e"
tag = "\x1a\xe1\x0b\x59\x4f\x09\xe2\x6a\x7e\x90\x2e\xcb\xd0\x60\x06\x91"
tagX = "\xc0\x87\x59\x24\xc1\xc7\x98\x79\x47\xde\xaf\xd8\x78\x0a\xcf\x49"
nonce1 = "\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"
nonce2 = "\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"
nonce3 = "\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"
Expand All @@ -31,6 +34,8 @@ nonce10 = "\xff\xff\xff\xff\xff\xff\xff\xff"
tests = testGroup "ChaChaPoly1305"
[ testCase "V1" runEncrypt
, testCase "V1-decrypt" runDecrypt
, testCase "V1-extended" runEncryptX
, testCase "V1-extended-decrypt" runDecryptX
, testCase "nonce increment" runNonceInc
]
where runEncrypt =
Expand All @@ -41,6 +46,14 @@ tests = testGroup "ChaChaPoly1305"
in propertyHoldCase [ eqTest "ciphertext" ciphertext out
, eqTest "tag" tag (B.convert outtag)
]
runEncryptX =
let ini = throwCryptoError $ AEAD.initializeX key (throwCryptoError $ AEAD.nonce24 ivX)
afterAAD = AEAD.finalizeAAD (AEAD.appendAAD aad ini)
(out, afterEncrypt) = AEAD.encrypt plaintext afterAAD
outtag = AEAD.finalize afterEncrypt
in propertyHoldCase [ eqTest "ciphertext" ciphertextX out
, eqTest "tag" tagX (B.convert outtag)
]

runDecrypt =
let ini = throwCryptoError $ AEAD.initialize key (throwCryptoError $ AEAD.nonce8 constant iv)
Expand All @@ -51,6 +64,15 @@ tests = testGroup "ChaChaPoly1305"
, eqTest "tag" tag (B.convert outtag)
]

runDecryptX =
let ini = throwCryptoError $ AEAD.initializeX key (throwCryptoError $ AEAD.nonce24 ivX)
afterAAD = AEAD.finalizeAAD (AEAD.appendAAD aad ini)
(out, afterDecrypt) = AEAD.decrypt ciphertextX afterAAD
outtag = AEAD.finalize afterDecrypt
in propertyHoldCase [ eqTest "plaintext" plaintext out
, eqTest "tag" tagX (B.convert outtag)
]

runNonceInc =
let n1 = throwCryptoError . AEAD.nonce12 $ nonce1
n3 = throwCryptoError . AEAD.nonce12 $ nonce3
Expand Down

0 comments on commit 54bc6df

Please sign in to comment.