commit 981c2bde42fda3d5de966e2bd7a72aa552234735
parent 5a78edf198ec514771a118d8b04643b258fd8849
Author: Jared Tobin <jared@jtobin.io>
Date: Sat, 26 Aug 2023 09:07:53 -0230
Add 6.43.
Diffstat:
7 files changed, 203 insertions(+), 21 deletions(-)
diff --git a/cryptopals.cabal b/cryptopals.cabal
@@ -30,6 +30,8 @@ library
, Cryptopals.DH.Session
, Cryptopals.Digest.Pure.MD4
, Cryptopals.Digest.Pure.SHA
+ , Cryptopals.DSA
+ , Cryptopals.DSA.Attacks
, Cryptopals.MAC
, Cryptopals.MAC.Attacks
, Cryptopals.RSA
diff --git a/docs/s5.md b/docs/s5.md
@@ -393,7 +393,7 @@ actually I think I cribbed them from the Data.Binary internals):
let n = p * q
et = pred p * pred q
e = 3
- md = invmod e et
+ md = modinv e et
case md of
Nothing -> loop
Just d -> pure $ Keypair (Key d n) (Key e n)
@@ -415,7 +415,7 @@ Works fine:
"secret!"
The Cryptopals.RSA module exports the keygen, encrypt, and decrypt
-functions, as well as invmod and roll & unroll.
+functions, as well as modinv and roll & unroll.
#### 5.40
@@ -457,9 +457,9 @@ So, following the CRT construction:
> let ms2 = n0 * n1
>
> :{
- > let res = (roll c0 * ms0 * M.fromJust (invmod ms0 n0)
- > + roll c1 * ms1 * M.fromJust (invmod ms1 n1)
- > + roll c2 * ms2 * M.fromJust (invmod ms2 n2))
+ > let res = (roll c0 * ms0 * M.fromJust (modinv ms0 n0)
+ > + roll c1 * ms1 * M.fromJust (modinv ms1 n1)
+ > + roll c2 * ms2 * M.fromJust (modinv ms2 n2))
> `mod`
> (n0 * n1 * n2)
> :}
diff --git a/docs/s6.md b/docs/s6.md
@@ -100,7 +100,7 @@ and, in particular, the requisite broken verification. 'sign' and
'forge' in Cryptopals.RSA.Attacks implements the desired forging
function.
-Let's test it out the basic signing and verification functionality:
+Let's test out the basic signing and verification functionality:
> Keypair sec pub@(Pub e n) <- keygen 1024
> let msg = "hi mom"
@@ -118,6 +118,29 @@ and now the forgery, produced of course without the secret key:
> verify pub "hi mum" gis
False
+#### 6.43
+Parameter generation for DSA as detailed in
+[FIPS.186-4](https://nvlpubs.nist.gov/nistpubs/FIPS/NIST.FIPS.186-4.pdf#
+page=40) seems to be particularly annoying and unrewarding to implement,
+so I didn't bother with it. The rest of the protocol is pretty standard
+fare; Cryptopals.DSA implements 'keygen', 'sign', and 'verify'
+functionality.
+
+As for the attack here, if one knows the subkey/nonce he can trivially
+recover the private key via the relation given. Since the nonce is a
+16-bit word, it can easily be brute-forced. The 'fromsub' and 'recover'
+functions in Cryptopals.DSA.Attacks handle this:
+
+ > let sec@(Sec sk) = recover defaultParams rawmsg rawsig rawpub
+ > CS.sha1 . BL.fromStrict . B16.encodeBase16' $ RSA.unroll sk
+ 0954edd5e0afe5542a4adf012611a91912a3ec16
+
+We can log the nonce/subkey found and hardcode that in the 'sign'
+function to check that we get the same signature as well (it's 16575):
+
+ > sig <- sign defaultParams sec rawmsg gen
+ > sig == rawsig
+ True
diff --git a/lib/Cryptopals/DSA.hs b/lib/Cryptopals/DSA.hs
@@ -0,0 +1,104 @@
+module Cryptopals.DSA (
+ Params(..)
+ , defaultParams
+
+ , Keypair(..)
+ , Key(..)
+ , keygen
+
+ , Sig(..)
+ , sign
+ , verify
+ ) where
+
+import Control.Monad.Primitive
+import qualified Cryptopals.Digest.Pure.SHA as CS
+import qualified Cryptopals.DH as DH
+import qualified Cryptopals.RSA as RSA
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as BL
+import Numeric.Natural
+import qualified System.Random.MWC as MWC
+
+fi :: (Integral a, Num b) => a -> b
+fi = fromIntegral
+
+data Params = Params {
+ dsap :: Natural
+ , dsaq :: Natural
+ , dsag :: Natural
+ } deriving (Eq, Show)
+
+p :: Natural
+p = 0x800000000000000089e1855218a0e7dac38136ffafa72eda7859f2171e25e65eac698c1702578b07dc2a1076da241c76c62d374d8389ea5aeffd3226a0530cc565f3bf6b50929139ebeac04f48c3c84afb796d61e5a4f9a8fda812ab59494232c7d2b4deb50aa18ee9e132bfa85ac4374d7f9091abc3d015efc871a584471bb1
+
+q :: Natural
+q = 0xf4f47f05794b256174bba6e9b396a7707e563c5b
+
+g :: Natural
+g = 0x5958c9d3898b224b12672c0b98e06c60df923cb8bc999d119458fef538b8fa4046c8db53039db620c094c9fa077ef389b5322a559946a71903f990f1f7e0e025e2d7f7cf494aff1a0470f5b64c36b625a097f1651fe775323556fe00b3608c887892878480e99041be601a62166ca6894bdd41a7054ec89f756ba9fc95302291
+
+defaultParams :: Params
+defaultParams = Params p q g
+
+data Keypair = Keypair {
+ sec :: Key
+ , pub :: Key
+ } deriving (Eq, Show)
+
+data Key =
+ Pub Natural
+ | Sec Natural
+ deriving (Eq, Show)
+
+keygen :: PrimMonad m => Params -> MWC.Gen (PrimState m) -> m Keypair
+keygen Params {..} gen = do
+ x <- MWC.uniformRM (1, dsaq - 1) gen
+ let y = DH.modexp dsag x dsap
+ pure $ Keypair (Sec x) (Pub y)
+
+data Sig = Sig {
+ sigr :: Natural
+ , sigs :: Natural
+ } deriving (Eq, Show)
+
+sign
+ :: PrimMonad m
+ => Params
+ -> Key
+ -> BS.ByteString
+ -> MWC.Gen (PrimState m)
+ -> m Sig
+sign ps@Params {..} key msg gen = case key of
+ Pub {} -> error "sign: need secret key"
+ Sec x -> do
+ k <- MWC.uniformRM (1, dsaq - 1) gen
+ let r = DH.modexp dsag k p `rem` dsaq
+ if r == 0
+ then sign ps key msg gen
+ else do
+ let h = fi . CS.integerDigest . CS.sha1 $ BL.fromStrict msg
+ s = (RSA.modinv' k dsaq * (h + x * r)) `rem` dsaq
+ if s == 0
+ then sign ps key msg gen
+ else pure (Sig r s)
+
+verify
+ :: Params
+ -> Key
+ -> BS.ByteString
+ -> Sig
+ -> Bool
+verify Params {..} key msg Sig {..} = case key of
+ Sec {} -> error "verify: need public key"
+ Pub y
+ | or [sigr == 0, sigr >= dsaq, sigs == 0, sigs >= dsaq] -> False
+ | otherwise ->
+ let w = RSA.modinv' sigs dsaq
+ h = fi . CS.integerDigest . CS.sha1 $ BL.fromStrict msg
+ u1 = (h * w) `rem` dsaq
+ u2 = (sigr * w) `rem` dsaq
+ v = (((DH.modexp dsag u1 dsap) * (DH.modexp y u2 dsap)) `rem` dsap)
+ `rem` dsaq
+ in v == sigr
+
diff --git a/lib/Cryptopals/DSA/Attacks.hs b/lib/Cryptopals/DSA/Attacks.hs
@@ -0,0 +1,53 @@
+module Cryptopals.DSA.Attacks where
+
+import qualified Control.Monad.ST as ST
+import qualified Cryptopals.DH as DH
+import qualified Cryptopals.Digest.Pure.SHA as CS
+import Cryptopals.DSA
+import qualified Cryptopals.RSA as RSA
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as BL
+import GHC.Word (Word16)
+import Numeric.Natural
+import qualified System.Random.MWC as MWC
+
+-- recover private key given a subkey
+fromsub :: Params -> BS.ByteString -> Sig -> Natural -> Key
+fromsub Params {..} msg Sig {..} k =
+ let h = fromIntegral . CS.integerDigest . CS.sha1 $ BL.fromStrict msg
+ num = (sigs * k - h) `rem` dsaq
+ den = RSA.modinv' sigr dsaq
+ in Sec $ (num * den) `rem` dsaq
+
+-- brute-force a private key with a Word16 subkey
+recover :: Params -> BS.ByteString -> Sig -> Key -> Key
+recover ps@Params {..} msg sig pub = ST.runST $ do
+ gen <- MWC.create
+ loop 2 gen
+ where
+ p = case pub of
+ Sec {} -> error "recover: need public key"
+ Pub pb -> pb
+ loop :: forall s. Word16 -> MWC.Gen s -> ST.ST s Key
+ loop k g = do
+ let sk@(Sec x) = fromsub ps msg sig (fromIntegral k)
+ sig' <- sign ps sk msg g
+ if DH.modexp dsag x dsap == p && verify ps pub msg sig'
+ then pure sk
+ else loop (succ k) g
+
+rawmsg :: BS.ByteString
+rawmsg = mconcat [
+ "For those that envy a MC it can be hazardous to your health\n"
+ , "So be friendly, a matter of life and death, just like a etch-a-sketch\n"
+ ]
+
+rawpub :: Key
+rawpub = Pub 0x84ad4719d044495496a3201c8ff484feb45b962e7302e56a392aee4abab3e4bdebf2955b4736012f21a08084056b19bcd7fee56048e004e44984e2f411788efdc837a0d2e5abb7b555039fd243ac01f0fb2ed1dec568280ce678e931868d23eb095fde9d3779191b8c0299d6e07bbb283e6633451e535c45513b2d33c99ea17
+
+rawsig :: Sig
+rawsig = Sig {
+ sigr = 548099063082341131477253921760299949438196259240
+ , sigs = 857042759984254168557880549501802188789837994940
+ }
+
diff --git a/lib/Cryptopals/RSA.hs b/lib/Cryptopals/RSA.hs
@@ -10,8 +10,8 @@ module Cryptopals.RSA (
, unroll'
, roll'
- , invmod
- , invmod'
+ , modinv
+ , modinv'
, encrypt
, decrypt
@@ -25,9 +25,9 @@ module Cryptopals.RSA (
, verify
) where
+import qualified Crypto.Number.Prime as P
import qualified Cryptopals.DH as DH
import qualified Cryptopals.Digest.Pure.SHA as CS
-import qualified Crypto.Number.Prime as P
import qualified Data.Binary as DB
import qualified Data.Bits as B
import qualified Data.ByteString as BS
@@ -69,7 +69,7 @@ roll' :: BS.ByteString -> Natural
roll' = BS.foldr unstep 0 where
unstep b a = a `B.shiftL` 8 B..|. fromIntegral b
--- egcd/invmod adapted from https://rosettacode.org/wiki/Modular_inverse
+-- egcd/modinv adapted from https://rosettacode.org/wiki/Modular_inverse
-- for a, b, return x, y, g such that ax + by = g for g = gcd(a, b)
egcd :: Integer -> Integer -> (Integer, Integer, Integer)
@@ -80,8 +80,8 @@ egcd a b =
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)
+modinv :: Natural -> Natural -> Maybe Natural
+modinv (fromIntegral -> a) (fromIntegral -> m)
| g == 1 = Just (pos i)
| otherwise = Nothing
where
@@ -90,11 +90,11 @@ invmod (fromIntegral -> a) (fromIntegral -> m)
| x < 0 = fromIntegral (x + m)
| otherwise = fromIntegral x
--- unsafe invmod
-invmod' :: Natural -> Natural -> Natural
-invmod' a m = case invmod a m of
+-- unsafe modinv
+modinv' :: Natural -> Natural -> Natural
+modinv' a m = case modinv a m of
Just x -> x
- Nothing -> error "invmod': no modular inverse"
+ Nothing -> error "modinv': no modular inverse"
data Key =
Sec Natural Natural
@@ -114,7 +114,7 @@ keygen siz = loop where
let n = p * q
et = pred p * pred q
e = 3
- md = invmod e et
+ md = modinv e et
case md of
Nothing -> loop
Just d -> pure $ Keypair (Sec d n) (Pub e n)
diff --git a/lib/Cryptopals/RSA/Attacks.hs b/lib/Cryptopals/RSA/Attacks.hs
@@ -38,9 +38,9 @@ e3BroadcastAttack (c0, p0) (c1, p1) (c2, p2) = case (p0, p1, p2) of
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
+ s = roll c0 * ms0 * modinv' ms0 n0
+ + roll c1 * ms1 * modinv' ms1 n1
+ + roll c2 * ms2 * modinv' ms2 n2
c = s `mod` (n0 * n1 * n2)
@@ -106,7 +106,7 @@ umrrecover
-> 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
+ Pub e n -> unroll $ (roll msg `mod` n * modinv' s n) `mod` n
-- bleichenbacher's e=3 signature forgery