cryptopals

Matasano's cryptopals challenges (cryptopals.com).
git clone git://git.jtobin.io/cryptopals.git
Log | Files | Refs | README | LICENSE

s6.md (9986B)


      1 #### 6.41
      2 
      3 For this one we'll just simulate the network stuff.
      4 Cryptopals.RSA.Attacks implements 'umrOracle', the simulated
      5 client/server interaction, as well as 'umrperturb', a function for
      6 'perturbing' collected ciphertexts, and 'umrrecover', a function for
      7 recovering plaintexts from the oracle's response.
      8 
      9 The more interesting part of this challenge is understanding the modular
     10 arithmetic going on. We have, for plaintext p and ciphertext c:
     11 
     12     c = p ^ e mod n
     13     p = c ^ d mod n
     14 
     15 Now, encrypt a random 's' under the same pubkey. We have:
     16 
     17     t = s ^ e mod n
     18     s = t ^ d mod n
     19 
     20 and now note that:
     21 
     22     (c t) mod n = (m ^ e mod n) (s ^ e mod n)
     23                 = (m s) ^ e mod n
     24 
     25 since exponentiation distributes over multiplication. If we have an
     26 arbitrary decryption oracle, then we can get:
     27 
     28     p' = (c t) ^ d mod n
     29        = ((c ^ d mod n) (t ^ d mod n)) mod n
     30        = (p s) mod n
     31 
     32 such that, for q the multiplicative inverse of s = t ^ d modulo n:
     33 
     34     p = p' q mod n.
     35 
     36 So, let's generate a keypair and kick off the oracle. There are a lot of
     37 really long lines here so I'll abbreviate the logs accordingly:
     38 
     39     > per <- keygen 1024
     40     > evalStateT (runEffect (umrOracle per)) mempty
     41 
     42 It prints out the generated public key for convenience:
     43 
     44     (cryptopals) umr-oracle: running with public key
     45     Pub 3 22513321964659585055936315428684912055916908912276341574563352485..
     46     (cryptopals) umr-oracle: awaiting hex-encoded input
     47 
     48 In another GHCi session we can mimic a user inputting their deepest, darkest
     49 secrets:
     50 
     51     > let msg = "my secret crush is so-and-so"
     52     > let pub = <above logged pubkey>
     53     > let cip = encrypt pub msg
     54 
     55 Hex-encoding the ciphertext and submitting it, the oracle spits out the
     56 hex-encoded plaintext:
     57 
     58     (cryptopals) umr-oracle: decrypted text
     59     6d792073656372657420637275736820697320736f2d616e642d736f
     60 
     61 and submitting it again (say, now, we're Mallory) yields nothing:
     62 
     63     (cryptopals) umr-oracle: rejecting request
     64     (cryptopals) umr-oracle: awaiting hex-encoded input
     65 
     66 So now we go and adjust the ciphertext via 'umrperturb', which returns
     67 the randomly generated number and the perturbed ciphertext (both of
     68 which are way too long to print here):
     69 
     70     > gen <- MWC.createSystemRandom
     71     > (s, c') <- umrperturb pub cip gen
     72 
     73 We hex-encode c' and submit it to the oracle again, this time receiving
     74 a different hex-encoded plaintext back. This one is very long, since,
     75 via our math above, it's a product of big integers:
     76 
     77     (cryptopals) umr-server: decrypted text
     78     c49c9dac3b7b4a86bf29eebafb3650469a5b91bf23c5339043ff9b72895953a21ff157f8..
     79 
     80 Calling the hex-decoded bytestring p', we can feed it into 'umrrecover'
     81 to crack the juicy secret:
     82 
     83     > umrrecover pub s p'
     84     "my secret crush is so-and-so"
     85 
     86 Shame, shame.
     87 
     88 #### 6.42
     89 
     90 The idea here is simple, but clever: assemble something that, to a
     91 sloppy verifier, looks to be validly PKCS#1 v1.5-encoded, put a bunch
     92 of junk bytes at the end of it, and manipulate everything such that
     93 the result is a cube (or at least has an approximate cube root). Then
     94 calculate the approximate cube root and pass that off as a signature.
     95 
     96 Cryptopals.RSA implements some functions for PKCS#1 v1.5 encoding (as
     97 defined in [RFC-2313](https://datatracker.ietf.org/doc/html/rfc2313)),
     98 and, in particular, the requisite broken verification. 'sign' and
     99 'verify' implement a signature scheme using that encoding and SHA512.
    100 'forge' in Cryptopals.RSA.Attacks implements the desired forging
    101 function.
    102 
    103 Let's test out the basic signing and verification functionality:
    104 
    105     > Keypair sec pub@(Pub e n) <- keygen 1024
    106     > let msg = "hi mom"
    107     > let (_, sig) = sign sec msg
    108     > verify pub msg sig
    109     True
    110     > verify pub "hi mum" sig
    111     False
    112 
    113 and now the forgery, produced of course without the secret key:
    114 
    115     > let gis = forge n msg
    116     > verify pub msg gis
    117     True
    118     > verify pub "hi mum" gis
    119     False
    120 
    121 #### 6.43
    122 
    123 Parameter generation for DSA as detailed in
    124 [FIPS.186-4](https://nvlpubs.nist.gov/nistpubs/FIPS/NIST.FIPS.186-4.pdf#page=40)
    125 seems to be particularly annoying and unrewarding to implement, so I
    126 didn't bother with it. The rest of the protocol is pretty standard fare;
    127 Cryptopals.DSA implements 'keygen', 'sign', and 'verify' functionality.
    128 
    129 As for the attack here, if one knows the subkey/nonce he can trivially
    130 recover the private key:
    131 
    132     s   = k^{-1} (h + x r)  (mod q)
    133     s k = h + x r           (mod q)
    134     x r = s k - h           (mod q)
    135     x   = r^{-1} (s k - h)  (mod q)
    136 
    137 Since the nonce here is a 16-bit word, it can easily be brute-forced.
    138 The 'fromsub' and 'recover' functions in Cryptopals.DSA.Attacks handle
    139 this:
    140 
    141     > let sec@(Sec sk) = recover defaultParams rawmsg rawsig rawpub
    142     > CS.sha1 . BL.fromStrict . B16.encodeBase16' $ RSA.unroll sk
    143     0954edd5e0afe5542a4adf012611a91912a3ec16
    144 
    145 We can log the nonce/subkey found (it's 16575) and hardcode that in the
    146 'sign' function to check that we get the same signature as well:
    147 
    148     > sig <- sign defaultParams sec rawmsg gen
    149     > sig == rawsig
    150     True
    151 
    152 #### 6.44
    153 
    154 A reused nonce results in an identical 'r' in the DSA signature
    155 produced, since 'r' depends only on the nonce and DSA domain parameters.
    156 Then for two signatures s1 and s2, "integerized" digests h1 and h2, and
    157 private key 'x', we have:
    158 
    159     s1 - s2 = k^{-1} (h1 + x r) - k^{-1} (h2 + x r)   (mod q)
    160             = k^{-1} (h1 + x r - h2 - x r)            (mod q)
    161             = k^{-1} (h1 - h2)                        (mod q)
    162           k = (s1 - s2)^{-1} (h1 - h2)                (mod q)
    163 
    164 There are a few pairs of messages here with identical 'r' values
    165 in the associated signatures. Shove any pair of them into the
    166 Cryptopals.DSA.Attacks.recoverNonce function to recover the nonce used:
    167 
    168     > m1
    169     "Listen for me, you better listen for me now. "
    170     > m2
    171     "Pure black people mon is all I mon know. "
    172     > let k = recoverNonce defaultParams sig1 sig2 h1 h2
    173     108994997653034620063305500641348549625
    174     > let Sec sk = fromsub defaultParams m1 sig1 k
    175     > CS.sha1 . BL.fromStrict . B16.encodeBase16' $ RSA.unroll sk
    176     ca8f6f7c66fa362d40760d135b763eb8527d3d52
    177 
    178 #### 6.45
    179 
    180 (N.b., my original signing / verification code actually checked for
    181 bad signature values, so Cryptopals.DSA also exports 'unsafeSign' and
    182 'unsafeVerify' that don't do any checking.)
    183 
    184 If g = 0 then we trivially have that every signature will include an
    185 r = 0 (and an 's' that doesn't depend on the private key, but this is
    186 ancillary). Every signature will verify for every message.
    187 
    188 As an illustration, if badParams contains g = 0, then:
    189 
    190     > per <- keygen badParams gen
    191     > sig <- unsafeSign badParams (sec per) "hi there" gen
    192     Sig {sigr = 0, sigs = 840728545249248021778225505261898025031268238630}
    193     > unsafeVerify badParams (pub per) "hi there" sig
    194     True
    195     > unsafeVerify badParams (pub per) "hi there?" sig
    196     True
    197     > unsafeVerify badParams (pub per) "uh oh" sig
    198     True
    199 
    200 The case is much the same for g = p + 1, since r = 1 for every signature
    201 produced. Any public key generated with these parameters will equal 1,
    202 but the "magic signature" will work for DSA pubkeys generated with other
    203 'g' parameters, so long as they use g = p + 1 when actually verifying.
    204 For the magicsig and arbitrary k, and arbitrary pubkey y, we have that:
    205 
    206     r = y^k mod p                 (mod q)
    207 
    208     s = k^{-1} r                  (mod q)
    209 
    210 So, when verifying:
    211 
    212     w  = s^{-1}                   (mod q)
    213        = r^{-1} k                 (mod q)
    214 
    215     u2 = r w                      (mod q)
    216        = r r^{-1} k               (mod q)
    217        = k                        (mod q)
    218 
    219 and then for any u, we have:
    220 
    221     v  = (g^u y^u2) mod p         (mod q)
    222        = (g^u y^k) mod p          (mod q)
    223        = ((p + 1)^u y^k) mod p
    224        = y^k mod p                (mod q)
    225        = r
    226 
    227 so that the signature will verify for every message by construction.
    228 
    229 An illustration. First generate a keypair with normal, God-fearing
    230 parameters:
    231 
    232     > per <- keygen defaultParams gen
    233 
    234 Here's the magic signature-making function:
    235 
    236     magicsig :: Params -> Key -> Sig
    237     magicsig Params {..} key = case key of
    238       Sec {} -> error "magicsig: need public key"
    239       Pub pk ->
    240         let r = (DH.modexp pk 3 dsap) `mod` dsaq
    241             s = (r * RSA.modinv' 3 dsaq) `mod` dsaq
    242         in  Sig r s
    243 
    244 Here's a magic signature, again created with good parameters. It looks
    245 innocuous enough:
    246 
    247     > let mag = magicsig defaultParams (pub per)
    248     > mag
    249     Sig {
    250       , sigr = 133287944151296049966935050695452535070249494052
    251       , sigs = 976726778072038851349123290347619105095879778206
    252     }
    253 
    254 Now let's verify that signature against some strings, using bad
    255 parameters in which g = p + 1:
    256 
    257     > unsafeVerify otherBadParams (pub per) "Hello, world" mag
    258     True
    259     > unsafeVerify otherBadParams (pub per) "Goodbye, world" mag
    260     True
    261 
    262 Bad group!
    263 
    264 #### 6.46
    265 
    266 This one is super fun, as advertised, and another good illustration of
    267 how the slightest information leak can compromise an otherwise secure
    268 cryptographic scheme.
    269 
    270 Cryptopals.RSA.Attacks.parityOracle implements the oracle, and
    271 parityAttack the loop:
    272 
    273     parityOracle :: BS.ByteString -> Bool
    274     parityOracle cip =
    275       let msg = decrypt (sec consistentKey) cip
    276       in  B.testBit (roll msg) 0
    277 
    278     parityAttack :: Key -> BS.ByteString -> IO BS.ByteString
    279     parityAttack (Pub e n) cip = loop 0 n (roll cip) where
    280       loop i j c
    281         | j == i || j - i == 1 = pure (unroll j)
    282         | otherwise = do
    283             B8.putStrLn (unroll j)
    284             let d = (c * DH.modexp 2 e n) `mod` n
    285             if   parityOracle (unroll d)
    286             then loop (i + (j - i) `quot` 2) j d
    287             else loop i (j - (j - i) `quot` 2) d
    288 
    289 For 'mystery' our base64-encoded input, we get (via our "Hollywood
    290 decryption"):
    291 
    292     > let cip = encrypt (pub consistentKey) (B64.decodeBase64Lenient mystery)
    293     > parityAttack (pub consistentKey) cip
    294     [..]
    295     "That's why I found you don't play around with the Funky Cold Medin\\"
    296