commit 81575fff837bdf0b5666a5ef852000db57823308
parent 3e883defb0f3dc4b70804ad8522d31e1349230be
Author: Jared Tobin <jared@jtobin.io>
Date: Sun, 20 Aug 2023 19:31:59 -0230
Add 6.41.
Diffstat:
5 files changed, 214 insertions(+), 9 deletions(-)
diff --git a/README.md b/README.md
@@ -13,4 +13,5 @@ to build binaries. Use `cabal install` to (I think) dump them in
* [Problem Set 3](docs/s3.md)
* [Problem Set 4](docs/s4.md)
* [Problem Set 5](docs/s5.md)
+* [Problem Set 6](docs/s6.md)
diff --git a/cryptopals.cabal b/cryptopals.cabal
@@ -33,6 +33,7 @@ library
, Cryptopals.MAC
, Cryptopals.MAC.Attacks
, Cryptopals.RSA
+ , Cryptopals.RSA.Attacks
, Cryptopals.SRP
, Cryptopals.SRP.Simple
, Cryptopals.Stream.Attacks
diff --git a/docs/s6.md b/docs/s6.md
@@ -0,0 +1,87 @@
+#### 6.41
+
+For this one we'll just simulate the network stuff.
+Cryptopals.RSA.Attacks implements 'umrOracle', the simulated
+client/server interaction, as well as 'umrperturb', a function for
+'perturbing' collected ciphertexts, and 'umrrecover', a function for
+recovering plaintexts from the oracle's response.
+
+The more interesting part of this challenge is understanding the modular
+arithmetic going on. We have, for plaintext p and ciphertext c:
+
+ c = p ^ e mod n
+ p = c ^ d mod n
+
+Now, encrypt a random 's' under the same pubkey. We have:
+
+ t = s ^ e mod n
+ s = t ^ d mod n
+
+and now note that:
+
+ (c t) mod n = (m ^ e mod n) (s ^ e mod n)
+ = (m s) ^ e mod n
+
+since exponentiation distributes over multiplication. If we have an
+arbitrary decryption oracle, then we can get:
+
+ p' = (c t) ^ d mod n
+ = ((c ^ d mod n) (t ^ d mod n)) mod n
+ = (p s) mod n
+
+such that, for q the multiplicative inverse of s = t ^ d modulo n:
+
+ p = p' q mod n.
+
+So, let's generate a keypair and kick off the oracle. There are a lot of
+really long lines here so I'll abbreviate the logs accordingly:
+
+ > per <- keygen 1024
+ > evalStateT (runEffect (umrOracle per)) mempty
+
+It prints out the generated public key for convenience:
+
+ (cryptopals) umr-oracle: running with public key
+ Pub 3 22513321964659585055936315428684912055916908912276341574563352485..
+ (cryptopals) umr-oracle: awaiting hex-encoded input
+
+In another GHCi session we can mimic a user inputting their deepest, darkest
+secrets:
+
+ > let msg = "my secret crush is so-and-so"
+ > let pub = <above logged pubkey>
+ > let cip = encrypt pub msg
+
+Hex-encoding the ciphertext and submitting it, the oracle spits out the
+hex-encoded plaintext:
+
+ (cryptopals) umr-oracle: decrypted text
+ 6d792073656372657420637275736820697320736f2d616e642d736f
+
+and submitting it again (say, now, we're Mallory) yields nothing:
+
+ (cryptopals) umr-oracle: rejecting request
+ (cryptopals) umr-oracle: awaiting hex-encoded input
+
+So now we go and adjust the ciphertext via 'umrperturb', which returns
+the randomly generated number and the perturbed ciphertext (both of
+which are way too long to print here):
+
+ > gen <- MWC.createSystemRandom
+ > (s, c') <- umrperturb pub cip gen
+
+We hex-encode c' and submit it to the oracle again, this time receiving
+a different hex-encoded plaintext back. This one is very long, since,
+via our math above, it's a product of big integers:
+
+ (cryptopals) umr-server: decrypted text
+ c49c9dac3b7b4a86bf29eebafb3650469a5b91bf23c5339043ff9b72895953a21ff157f8..
+
+Calling the hex-decoded bytestring p', we can feed it into 'umrrecover'
+to crack the juicy secret:
+
+ > umrrecover pub s p'
+ "my secret crush is so-and-so"
+
+Shame, shame.
+
diff --git a/lib/Cryptopals/RSA.hs b/lib/Cryptopals/RSA.hs
@@ -7,6 +7,7 @@ module Cryptopals.RSA (
, roll
, invmod
+ , invmod'
, encrypt
, decrypt
) where
@@ -17,8 +18,6 @@ import qualified Data.Binary as DB
import qualified Data.Bits as B
import qualified Data.ByteString as BS
import Data.List (unfoldr)
-import qualified Data.Maybe as M
-import qualified Math.NumberTheory.Roots as R
import Numeric.Natural
-- | Simple little-endian ByteString encoding for Naturals.
@@ -41,14 +40,14 @@ roll = foldr unstep 0 . BS.unpack where
egcd :: Integer -> Integer -> (Integer, Integer, Integer)
egcd a 0 = (1, 0, a)
egcd a b =
- let (q, r) = a `quotRem` b
+ let (q, r) = a `quotRem` b
(s, t, g) = egcd b r
- in (t, s - q * t, g)
+ in (t, s - q * t, g)
-- for a, m return x such that ax = 1 mod m
invmod :: Natural -> Natural -> Maybe Natural
invmod (fromIntegral -> a) (fromIntegral -> m)
- | 1 == g = Just (pos i)
+ | g == 1 = Just (pos i)
| otherwise = Nothing
where
(i, _, g) = egcd a m
@@ -56,7 +55,14 @@ invmod (fromIntegral -> a) (fromIntegral -> m)
| x < 0 = fromIntegral (x + m)
| otherwise = fromIntegral x
-data Key = Key Natural Natural
+invmod' :: Natural -> Natural -> Natural
+invmod' a m = case invmod a m of
+ Just x -> x
+ Nothing -> error "invmod': no modular inverse"
+
+data Key =
+ Sec Natural Natural
+ | Pub Natural Natural
deriving (Eq, Show)
data Keypair = Keypair {
@@ -75,11 +81,15 @@ keygen siz = loop where
md = invmod e et
case md of
Nothing -> loop
- Just d -> pure $ Keypair (Key d n) (Key e n)
+ Just d -> pure $ Keypair (Sec d n) (Pub e n)
encrypt :: Key -> BS.ByteString -> BS.ByteString
-encrypt (Key e n) m = unroll (DH.modexp (roll m) e n)
+encrypt key msg = case key of
+ Sec {} -> error "encrypt: need public key"
+ Pub e n -> unroll (DH.modexp (roll msg) e n)
decrypt :: Key -> BS.ByteString -> BS.ByteString
-decrypt = encrypt
+decrypt key cip = case key of
+ Pub {} -> error "decrypt: need secret key"
+ Sec d n -> unroll (DH.modexp (roll cip) d n)
diff --git a/lib/Cryptopals/RSA/Attacks.hs b/lib/Cryptopals/RSA/Attacks.hs
@@ -0,0 +1,106 @@
+module Cryptopals.RSA.Attacks (
+ e3BroadcastAttack
+ ) where
+
+import Control.Monad (forever, when)
+import Control.Monad.Primitive
+import Control.Monad.IO.Class
+import Control.Monad.Trans.Class
+import Control.Monad.Trans.State
+import qualified Cryptopals.DH as DH
+import Cryptopals.RSA
+import qualified Cryptopals.Digest.Pure.SHA as CS
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Base16 as B16
+import qualified Data.ByteString.Char8 as B8
+import qualified Data.ByteString.Lazy as BL
+import qualified Data.Maybe as M
+import qualified Data.HashSet as HS
+import qualified Data.Text as T
+import qualified Data.Text.Encoding as TE
+import qualified Data.Text.IO as TIO
+import qualified Math.NumberTheory.Roots as R
+import Numeric.Natural
+import Pipes
+import qualified Pipes.Prelude as P
+import qualified System.Random.MWC as MWC
+
+e3BroadcastAttack
+ :: (BS.ByteString, Key) -- ciphertext / pubkey
+ -> (BS.ByteString, Key) -- ciphertext / pubkey
+ -> (BS.ByteString, Key) -- ciphertext / pubkey
+ -> BS.ByteString -- plaintext
+e3BroadcastAttack (c0, p0) (c1, p1) (c2, p2) = case (p0, p1, p2) of
+ (Pub _ n0, Pub _ n1, Pub _ n2) ->
+ let ms0 = n1 * n2
+ ms1 = n0 * n2
+ ms2 = n0 * n1
+
+ s = roll c0 * ms0 * invmod' ms0 n0
+ + roll c1 * ms1 * invmod' ms1 n1
+ + roll c2 * ms2 * invmod' ms2 n2
+
+ c = s `mod` (n0 * n1 * n2)
+
+ in unroll (R.integerCubeRoot c)
+
+ _ -> error "e3BroadcastAttack: require public keys"
+
+type Digests = HS.HashSet Integer
+
+umrClient :: MonadIO m => Key -> Producer BS.ByteString m ()
+umrClient pub = case pub of
+ Sec {} -> error "umrClient: need public key"
+ Pub {} -> do
+ liftIO $ do
+ TIO.putStrLn "(cryptopals) umr-oracle: running with public key"
+ TIO.putStrLn (T.pack $ show pub)
+ forever $ do
+ lin <- liftIO $ do
+ TIO.putStrLn "(cryptopals) umr-oracle: awaiting hex-encoded input"
+ BS.getLine
+ yield (B16.decodeBase16Lenient lin)
+
+umrServer :: Key -> Consumer BS.ByteString (StateT Digests IO) ()
+umrServer sec = case sec of
+ Pub {} -> error "umrServer: need secret key"
+ Sec {} -> forever $ do
+ cip <- await
+ digests <- lift get
+
+ let has = CS.integerDigest . CS.sha512 $ BL.fromStrict cip
+
+ if HS.member has digests
+ then liftIO $ TIO.putStrLn "(cryptopals) umr-oracle: rejecting request"
+ else do
+ lift $ modify (HS.insert has)
+ let msg = decrypt sec cip
+ liftIO $ do
+ TIO.putStrLn "(cryptopals) umr-oracle: decrypted text"
+ TIO.putStrLn (B16.encodeBase16 msg)
+
+umrOracle :: Keypair -> Effect (StateT Digests IO) ()
+umrOracle (Keypair sec pub) = umrClient pub >-> umrServer sec
+
+umrperturb
+ :: Key
+ -> BS.ByteString -- original ciphertext
+ -> MWC.Gen RealWorld
+ -> IO (Natural, BS.ByteString) -- (random s, perturbed ciphertext)
+umrperturb key cip gen = case key of
+ Sec {} -> error "umrperturb: need public key"
+ Pub e n -> do
+ s <- MWC.uniformRM (1, n - 1) gen
+ let c = roll cip
+ c' = (DH.modexp s e n * c) `mod` n
+ pure (s, unroll c')
+
+umrrecover
+ :: Key
+ -> Natural
+ -> BS.ByteString
+ -> BS.ByteString
+umrrecover key s msg = case key of
+ Sec {} -> error "umrrecover: need public key"
+ Pub e n -> unroll $ (roll msg `mod` n * invmod' s n) `mod` n
+