cryptopals

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

s3.md (10938B)


      1 ### Set 3
      2 
      3 #### 3.17
      4 
      5 This one took me some fiddling to get right. As stated in the challenge
      6 text itself, it's easy to get hung up on the idea of decrypting padding
      7 bytes themselves. But the idea is to choose ciphertext byte values so as
      8 to *force* valid padding in a "phantom" plaintext, then use the added
      9 information to recover the actual plaintext bytes (padding bytes or no).
     10 
     11 From the 2.16 answer text, CBC-mode decryption proceeds as follows:
     12 
     13     for ciphertext                    c = (c_0, c_1, c_2, .., c_l)
     14         block decryption w/key k      dec_k
     15         xor operator                  +
     16 
     17     let p_1 = dec_k(c_1) + c_0
     18         p_2 = dec_k(c_2) + c_1
     19         ..
     20         p_l = dec_k(c_l) + c_{l-1}
     21 
     22     in  plaintext                     p = (p_1, p_2, .., p_l)
     23 
     24 So, the last plaintext byte can be described by:
     25 
     26     lb(p_l) = lb(dec_k(c_1) + c_{l-1})      (1)
     27 
     28 Say one corrupts `c_{l-1}` (producing `c_{l-1}'`) by perturbing the last
     29 byte, and then submits `(c_{l-1}', c_l)` to the padding oracle. The
     30 padding oracle will internally compute:
     31 
     32     p_l' = dec_k(c_l) + c_{l-1}'
     33 
     34 and then check its padding. We want to *force* the last byte of `p_l'`
     35 to be 0x01, so we require that 1) the padding of `p_l'` validates, and
     36 2) that this forced padding is not 0x0202 or 0x030303 or some other
     37 scheme. We do this repeatedly until the padding validates as desired
     38 (if we are unlucky and have forced some other padding, e.g. 0x0202, we
     39 just treat that as a failure) yielding:
     40 
     41     lb(dec_k(c_l) + c_{l-1}')     = 0x01
     42     lb(dec_k(c_l)) + lb(c_{l-1}') = 0x01
     43 
     44 so that:
     45 
     46     lb(dec_k(c_l)) = lb(c_{l-1}') + 0x01
     47 
     48 and thus (using (1)), that:
     49 
     50     lb(p_l) = lb(dec_k(c_l)) + lb(c_{l-1)}
     51             = lb(c_{l-1}') + 0x01 + lb(c_{l}).
     52 
     53 The same is then true for every other byte. For the penultimate byte,
     54 for example, we want to *force* the penultimate byte of `p_l'` to be
     55 0x02, so we also require that the last byte of `p_l'` be 0x02 in order
     56 for its padding to validate. Each time we simply do this by manipulating
     57 `c_{l-1}` appropriately.
     58 
     59 `Cryptopals.Block.Attacks.paddingOracle` is a padding oracle, and the
     60 `Cryptopals.Block.Attacks.paddingOracleAttack` function implements the
     61 padding oracle attack (for arbitrary ciphertexts):
     62 
     63     > :{
     64     ghci| F.for_ [1..10] $ \_ -> putStrLn . show . M.fromJust =<<
     65     ghci|   fmap (CU.unpkcs7 . paddingOracleAttack) (paddingOracle gen)
     66     ghci| :}
     67     "000002Quick to the point, to the point, no faking"
     68     "000001With the bass kicked in and the Vega's are pumpin'"
     69     "000000Now that the party is jumping"
     70     "000000Now that the party is jumping"
     71     "000004Burning 'em, if you ain't quick and nimble"
     72     "000005I go crazy when I hear a cymbal"
     73     "000003Cooking MC's like a pound of bacon"
     74     "000002Quick to the point, to the point, no faking"
     75     "000003Cooking MC's like a pound of bacon"
     76     "000004Burning 'em, if you ain't quick and nimble"
     77 
     78 #### 3.18
     79 
     80 CTR mode is trivial; the only thing to get right is really the specified
     81 counter format. `Cryptopals.AES.decryptCtrAES128` (or its synonym,
     82 `encryptCtrAES128`) can be used to retrieve our desired plaintext:
     83 
     84     > let Right cip = B64.decodeBase64 "L77na/nrFsKvynd6HzOoG7GHTLXsTVu9qvY/2syLXzhPweyyMTJULu/6/kXX0KSvoOLSFQ=="
     85     > decryptCtrAES128 0 "YELLOW SUBMARINE" cip
     86     "Yo, VIP Let's kick it Ice, Ice, baby Ice, Ice, baby "
     87 
     88 You can get at this from the command line via the 'ctr' arg to the 'aes'
     89 binary:
     90 
     91     $ ct=$(echo "L77na/nrFsKvynd6HzOoG7GHTLXsTVu9qvY/2syLXzhPweyyMTJULu/6/kXX0KSvoOLSFQ==" | base64 -d | xxd -p | tr -d '\n')
     92     $ key=$(echo -n "YELLOW SUBMARINE" | xxd -p)
     93     $ aes decrypt ctr --nonce 0 "$key" "$ct" | xxd -r -p
     94     Yo, VIP Let's kick it Ice, Ice, baby Ice, Ice, baby
     95 
     96 #### 3.19 (and 3.20)
     97 
     98 I used the same approach as was done in question 1.6, taking the
     99 first 16 bytes of each ciphertext and then transposing them such that
    100 each "block" has been single-byte XOR'd by something. Using a similar
    101 scoring routine (see `Cryptopals.Block.Attacks.rnBest`) and some manual
    102 fiddling, one can recover the keystream without much difficulty. Finding
    103 the first 16 bytes exposes enough of the plaintexts that the remaining
    104 bytes can be completed by hand, though I bailed out after I got the
    105 gist of it:
    106 
    107     > let ks = BS.pack $ fmap (\(a, _, _) -> a) . rnBest) rnrotated
    108     > -- the resulting keystream needed some manual patching, but
    109     > -- results like "eighteeoth-centu" make it easy to do.
    110     > take 4 $ fmap (CU.fixedXor ks) rnscrypted
    111     ["I have met them ","Coming with vivi","From counter or ","Eighteenth-centu"]
    112 
    113 (It turns out this is the way one is supposed to solve 3.20 too.  Whoops!)
    114 
    115 #### 3.21
    116 
    117 `Cryptopals.Stream.RNG.MT19937` implements the Mersenne Twister
    118 (MT19937) PRNG in standard return-the-generator fashion:
    119 
    120     > let gen = seed 42
    121     > tap 3 gen
    122     > ([1608637542,3421126067,4083286876],<MT19937.Gen>)
    123 
    124 The only annoying thing about this problem was finding a test vector
    125 to check the implementation against. I used the outputs on [this
    126 guy's](https://create.stephan-brumme.com/mersenne-twister/) page;
    127 the implementations he cites return signed 32-bit integers, but I
    128 use (unsigned) Word32. One can convert results to e.g. Int32 with
    129 fromIntegral to verify.
    130 
    131 There's also a binary:
    132 
    133     $ mt19937 42 3
    134     1608637542
    135     3421126067
    136     4083286876
    137 
    138 (N.b., the [original
    139 paper](http://www.math.sci.hiroshima-u.ac.jp/m-mat/MT/ARTICLES/mt.pdf) on
    140 the Mersenne Twister is very well-written and readable.)
    141 
    142 #### 3.22
    143 
    144 After the fourth or fifth time my children woke me up in the middle of
    145 the night, I decided to just get up and pick at this stuff. I kicked off
    146 this business somewhere around 5-6am:
    147 
    148     $ sleep $(shuf -i 40-1000 -n 1); ts=$(date +%s); \
    149       sleep $(shuf -i 40-1000 -n 1); mt19937 $ts 1
    150     1133750118
    151 
    152 and then lay down again and fell asleep for a few hours. Using [this
    153 timestamp calculator](https://www.unixtimestamp.com/) after the fact,
    154 the timestamp is probably somewhere in the range of about \[1690702400,
    155 1690708000\].  So, using:
    156 
    157     #!/usr/bin/env bash
    158     declare -i i
    159     i=1690702400
    160     while (($i < 1690708000)); do
    161       val=$(mt19937 $i 1)
    162       if (($val == 1133750118)); then
    163         echo "seed is $i"
    164         exit
    165       else
    166         i+=1
    167       fi
    168     done
    169 
    170 we get:
    171 
    172     $ ./crackmt.sh
    173     seed is 1690706100
    174 
    175 So, via the same timestamp calculator, it was seeded at Sun Jul 30 2023
    176 06:05:00 GMT-0230 (heure d’été de Terre-Neuve).
    177 
    178 #### 3.23
    179 
    180 A Mersenne Twister outputs elements of its internal state transformed
    181 by a linear tempering map. The state is perturbed every 624 iterations
    182 (the "twist"), but if we have all 624 outputs generated from a constant
    183 internal state, that state can be recovered by running the outputs
    184 through the inverse tempering map.
    185 
    186 The tempering transform (in Cryptopals.Stream.RNG.MT19937) can be
    187 expressed by:
    188 
    189     temper :: Word32 -> Word32
    190     temper = e4 . e3 . e2 . e1 where
    191       e1 = rs u
    192       e2 = ls s b
    193       e3 = ls t c
    194       e4 = rs l
    195 
    196 and its inverse by:
    197 
    198     untemper :: Word32 -> Word32
    199     untemper = n1 . n2 . n3 . n4 where
    200       n1 = rsinv u
    201       n2 = lsinv s b
    202       n3 = lsinv t c
    203       n4 = rsinv l
    204 
    205 given the following salad of internal functions (you either know how to invert
    206 an xorshift operation or you don't):
    207 
    208     ls :: Word32 -> Word32 -> Word32 -> Word32
    209     ls s m a = a `B.xor` (B.shiftL a (fi s) .&. m)
    210 
    211     rs :: Word32 -> Word32 -> Word32
    212     rs s a = a `B.xor` B.shiftR a (fi s)
    213 
    214     lsinv :: Word32 -> Word32 -> Word32 -> Word32
    215     lsinv s bm = loop 0 where
    216       loop j !b
    217         | j >= fi w = b
    218         | otherwise =
    219             let m = mask j (min (fi w - 1) (j + fi s - 1))
    220                 x = ((m .&. b) `B.shiftL` fi s) .&. bm
    221             in  loop (j + fi s) (b `B.xor` x)
    222 
    223     rsinv :: Word32 -> Word32 -> Word32
    224     rsinv s = loop (fi w - 1) where
    225       loop j !b
    226         | j <= 0    = b
    227         | otherwise =
    228             let m = mask (max 0 (j - fi s + 1)) j
    229                 x = (m .&. b) `B.shiftR` fi s
    230             in  loop (j - fi s) (b `B.xor` x)
    231 
    232     mask :: B.Bits b => Int -> Int -> b
    233     mask l h = loop l B.zeroBits where
    234       loop j !b
    235         | j > h = b
    236         | otherwise =
    237             loop (succ j) (B.setBit b j)
    238 
    239 So we can run a generator for 624 iterations, capture the outputs, and
    240 untemper them to recover the internal state for those 624 iterations
    241 (with the caveat that the outputs we need to observe must occur absent
    242 any intermediate twists of the internal state):
    243 
    244     > let gen = seed 42
    245     > let (bs, g) = tap 624 gen
    246     > let cloned = Gen 624 (VU.fromList . fmap untemper $ bs)
    247     > fst (tap 3 g)
    248     [108880612,791707097,4134543476]
    249     > fst (tap 3 cloned)
    250     [108880612,791707097,4134543476]
    251 
    252 As stated in sec 1.6 of the original Mersenne Twister paper, the key
    253 to hardening the PRNG is to pass the outputs through a secure hash
    254 function.
    255 
    256 #### 3.24
    257 
    258 The first challenge here is to recover the stream cipher's seed from
    259 some ciphertext, given a (mostly-) known plaintext. The issue is that
    260 at 16 bits the seed is tiny, and so it can be easily be brute-forced by
    261 just iterating through the possible word values:
    262 
    263     mtCipherAttack :: BS.ByteString -> Word16
    264     mtCipherAttack cip = loop 0 where
    265       l = BS.length cip
    266       t = BS.replicate 14 65
    267       loop j
    268         | j > (maxBound :: Word16) = error "impossible seed"
    269         | otherwise =
    270             let g  = MT.seed (fromIntegral j)
    271                 bs = keystream l g
    272                 pt = BS.drop (l - 14) (bs `CU.fixedXor` cip)
    273             in  if   pt == t
    274                 then j
    275                 else loop (succ j)
    276 
    277 Running it on some ciphertext I created reveals the seed used in a
    278 minute or two:
    279 
    280     > B16.encodeBase16 ciphertext
    281     "df2c20f5025fed9e86a986e47d8bee063213afc1"
    282     > mtCipherAttack ciphertext
    283     50000
    284 
    285 The token seeded by system time is also trivial to crack, since we can
    286 just generate a seed from the current time and check the result directly:
    287 
    288     pwntToken :: IO T.Text
    289     pwntToken = do
    290       s <- fmap (fromIntegral . TS.systemSeconds) TS.getSystemTime
    291       let g = MT.seed s
    292       pure $ B64.encodeBase64 (keystream 16 g)
    293 
    294     notPwntToken :: IO T.Text
    295     notPwntToken = do
    296       g  <- MWC.createSystemRandom
    297       bs <- fmap BS.pack $ replicateM 16 (MWC.uniformR (32, 126) g)
    298       pure $ B64.encodeBase64 bs
    299 
    300     isPwnt :: T.Text -> IO Bool
    301     isPwnt token = do
    302       s <- fmap (fromIntegral . TS.systemSeconds) TS.getSystemTime
    303       let g = MT.seed s
    304           ks = keystream 16 g
    305       pure $ token == B64.encodeBase64 ks
    306 
    307 (N.b., 'notPwntToken' uses /dev/random or /dev/urandom to generate a
    308 seed, instead of the system time.)
    309 
    310 Some examples:
    311 
    312     > pwntToken
    313     "2Pi2LO0cn3XXyw1xwrLlHQ=="
    314     > pwntToken
    315     "WqPvmtGTfc3QkhVs78uOqQ=="
    316     > notPwntToken
    317     "V0codSgtXyNvLSJ4XjNyNQ=="
    318     > notPwntToken
    319     "STA3ZnxVe1tQW0Q4TF0pbg=="
    320     > pwntToken >>= isPwnt
    321     True
    322     > notPwntToken >>= isPwnt
    323     False
    324