commit 6d9fe4a9745599ac6c6101a579d2d108b5720828
parent 12e1863607af0f8ace4e26f766eadb64a01de79e
Author: Jared Tobin <jared@jtobin.io>
Date: Mon, 10 Mar 2025 16:06:57 +0400
lib: decrypt
Diffstat:
2 files changed, 41 insertions(+), 11 deletions(-)
diff --git a/lib/Crypto/AEAD/ChaCha20Poly1305.hs b/lib/Crypto/AEAD/ChaCha20Poly1305.hs
@@ -3,7 +3,14 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
-module Crypto.AEAD.ChaCha20Poly1305 where
+module Crypto.AEAD.ChaCha20Poly1305 (
+ -- * AEAD construction
+ encrypt
+ , decrypt
+
+ -- testing
+ , _poly1305_key_gen
+ ) where
import qualified Crypto.Cipher.ChaCha20 as ChaCha20
import qualified Crypto.MAC.Poly1305 as Poly1305
@@ -34,17 +41,22 @@ unroll8 (unroll -> u@(BI.PS _ _ l))
| otherwise = u
{-# INLINE unroll8 #-}
-poly1305_key_gen
+-- RFC8439 2.6
+
+_poly1305_key_gen
:: BS.ByteString -- ^ 256-bit initial keying material
-> BS.ByteString -- ^ 96-bit nonce
-> BS.ByteString -- ^ 256-bit key (suitable for poly1305)
-poly1305_key_gen key@(BI.PS _ _ l) nonce
+_poly1305_key_gen key@(BI.PS _ _ l) nonce
| l /= 32 = error "ppad-aead (poly1305_key_gen): invalid key"
| otherwise = BS.take 32 (ChaCha20.block key 0 nonce)
-{-# INLINEABLE poly1305_key_gen #-}
+{-# INLINEABLE _poly1305_key_gen #-}
pad16 :: BS.ByteString -> BS.ByteString
pad16 (BI.PS _ _ l) = BS.replicate (16 - l `rem` 16) 0
+{-# INLINE pad16 #-}
+
+-- RFC8439 2.8
encrypt
:: BS.ByteString -- ^ arbitrary-length additional authenticated data
@@ -52,14 +64,14 @@ encrypt
-> BS.ByteString -- ^ 64-bit initial value (IV)
-> BS.ByteString -- ^ 32-bit salt
-> BS.ByteString -- ^ arbitrary-length plaintext
- -> (BS.ByteString, BS.ByteString) -- ^ (ciphertext, MAC)
+ -> (BS.ByteString, BS.ByteString) -- ^ (ciphertext, 128-bit MAC)
encrypt aad key iv salt plaintext
| BS.length key /= 32 = error "ppad-aead (encrypt): invalid key"
| BS.length iv /= 8 = error "ppad-aead (encrypt): invalid IV"
| BS.length salt /= 4 = error "ppad-aead (encrypt): invalid salt"
| otherwise =
let nonce = salt <> iv
- otk = poly1305_key_gen key nonce
+ otk = _poly1305_key_gen key nonce
ciphertext = ChaCha20.cipher key 1 nonce plaintext
md0 = aad <> pad16 aad
md1 = md0 <> ciphertext <> pad16 ciphertext
@@ -68,3 +80,17 @@ encrypt aad key iv salt plaintext
tag = Poly1305.mac otk md3
in (ciphertext, tag)
+decrypt
+ :: BS.ByteString -- ^ arbitrary-length additional authenticated data
+ -> BS.ByteString -- ^ 256-bit key
+ -> BS.ByteString -- ^ 64-bit initial value (IV)
+ -> BS.ByteString -- ^ 32-bit salt
+ -> (BS.ByteString, BS.ByteString) -- ^ (arbitrary-length ciphertext, 128-bit MAC)
+ -> Either BS.ByteString BS.ByteString -- ^ possibly-authenticated plaintext
+decrypt aad key iv salt (ciphertext, mac) =
+ let (plaintext, _) = encrypt aad key iv salt ciphertext
+ (_, tag) = encrypt aad key iv salt plaintext -- XX seems wrong?
+ in if mac == tag
+ then Right plaintext
+ else Left plaintext
+
diff --git a/test/Main.hs b/test/Main.hs
@@ -14,7 +14,7 @@ import qualified Test.Tasty.HUnit as H
main :: IO ()
main = defaultMain $ testGroup "ppad-aead" [
poly1305_key_gen
- , encrypt
+ , crypt
]
poly1305_key_gen :: TestTree
@@ -27,11 +27,11 @@ poly1305_key_gen = H.testCase "poly1305_key_gen" $ do
Just e = B16.decode
"8ad5a08b905f81cc815040274ab29471a833b637e3fd0da508dbb8e2fdd1a646"
- o = AEAD.poly1305_key_gen key non
+ o = AEAD._poly1305_key_gen key non
H.assertEqual mempty e o
-encrypt :: TestTree
-encrypt = H.testCase "encrypt" $ do
+crypt :: TestTree
+crypt = H.testCase "encrypt/decrypt" $ do
let (o_cip, o_tag) = AEAD.encrypt aad key iv salt sunscreen
e_cip = fromJust . B16.decode $
@@ -40,7 +40,12 @@ encrypt = H.testCase "encrypt" $ do
e_tag = fromJust . B16.decode $
"1ae10b594f09e26a7e902ecbd0600691"
+ o_dec = AEAD.decrypt aad key iv salt (o_cip, o_tag)
+ o_fal = AEAD.decrypt aad key iv salt (o_cip, BS.replicate 16 0)
+
H.assertEqual mempty (e_cip, e_tag) (o_cip, o_tag)
+ H.assertEqual mempty (Right sunscreen) o_dec
+ H.assertEqual mempty (Left sunscreen) o_fal
where
sunscreen :: BS.ByteString
sunscreen = fromJust . B16.decode $
@@ -53,4 +58,3 @@ encrypt = H.testCase "encrypt" $ do
iv = fromJust . B16.decode $ "4041424344454647"
salt = fromJust . B16.decode $ "07000000"
-