cryptopals

Matasano's cryptopals challenges (cryptopals.com).
Log | Files | Refs | README | LICENSE

commit 769f94dcd712b2f1903c322f1544dd0bcb7d05ec
parent 46476d6f71955fc525cd73e1d529d7569e498977
Author: Jared Tobin <jared@jtobin.io>
Date:   Thu,  1 Jun 2023 20:29:27 +0400

Add single-byte XOR deciphering utility.

Diffstat:
Mcryptopals.cabal | 1+
Mlib/Cryptopals/Util.hs | 6++----
Mlib/Cryptopals/Util/Similarity.hs | 4++--
Msrc/BreakSingleByteXor.hs | 37+++++++++++++++++++++----------------
4 files changed, 26 insertions(+), 22 deletions(-)

diff --git a/cryptopals.cabal b/cryptopals.cabal @@ -49,6 +49,7 @@ executable break-single-byte-xor hs-source-dirs: src build-depends: base + , base16 , bytestring , cryptopals , optparse-applicative diff --git a/lib/Cryptopals/Util.hs b/lib/Cryptopals/Util.hs @@ -30,8 +30,6 @@ hexToB64 (Hex b) = do fixedXor :: BS.ByteString -> BS.ByteString -> BS.ByteString fixedXor l r = BS.pack $ BS.zipWith B.xor l r -singleByteXor :: Word8 -> Hex -> Either T.Text Hex -singleByteXor byt (Hex bs) = do - s <- B16.decodeBase16 bs - pure $ Hex (B16.encodeBase16' . BS.map (B.xor byt) $ s) +singleByteXor :: Word8 -> BS.ByteString -> BS.ByteString +singleByteXor byt = BS.map (B.xor byt) diff --git a/lib/Cryptopals/Util/Similarity.hs b/lib/Cryptopals/Util/Similarity.hs @@ -13,7 +13,7 @@ mse :: IMS.IntMap Double -> IMS.IntMap Double -> Double mse ref tar = let res = IMS.foldlWithKey' alg mempty ref siz = IMS.size res - in IMS.foldl' (\acc val -> (acc + val) / fromIntegral siz) 0 res + in IMS.foldl' (\acc val -> acc + val / fromIntegral siz) 0 res where alg acc key val = case IMS.lookup key tar of Nothing -> acc @@ -35,7 +35,7 @@ normalize m = -- | Observed frequency distribution of bytes in English corpora. english :: IMS.IntMap Double -english = IMS.fromList [ +english = IMS.fromAscList [ (9, 0.000057) , (23, 0.000000) , (32, 0.171662) diff --git a/src/BreakSingleByteXor.hs b/src/BreakSingleByteXor.hs @@ -3,15 +3,16 @@ module Main where -import Control.Monad (unless) import qualified Cryptopals.Util as CU import qualified Data.ByteString as BS +import qualified Data.ByteString.Base16 as B16 import Data.List (foldl') import qualified Data.Text as T import qualified Data.Text.IO as TIO import qualified Data.Text.Encoding as TE import GHC.Word (Word8) import qualified Options.Applicative as O +import qualified System.Exit as SE import qualified System.IO as SIO data Args = Args { argsInp :: T.Text } @@ -28,29 +29,33 @@ best s = foldl' alg (0, CU.score s, s) [32..126] where then (b, sc, xo) else acc -render :: Show a => a -> T.Text -render = T.pack. show - decipher :: Args -> IO () decipher Args {..} = do - let s = TE.encodeUtf8 argsInp + let render :: Show a => a -> T.Text + render = T.pack . show + + err = TIO.hPutStrLn SIO.stderr + out = TIO.hPutStrLn SIO.stdout - TIO.hPutStrLn SIO.stderr $ - "cryptopals: input similarity score is " <> render (CU.score s) + args = B16.decodeBase16 $ TE.encodeUtf8 argsInp - let (byt, bsc, b) = best s + case args of + Left e -> do + err $ "cryptopals: " <> e + SE.exitFailure - unless (b == s) $ do + Right s -> do + err $ "cryptopals: input similarity score is " <> render (CU.score s) - TIO.hPutStrLn SIO.stderr ( - "cryptopals: xor-ing with " <> render byt <> - " yields score " <> render bsc - ) + let (byt, bsc, b) = best s - TIO.hPutStrLn SIO.stderr $ - "cryptopals: result" + err ( + "cryptopals: xor-ing with " <> render byt <> + " yields " <> render bsc + ) - TIO.hPutStrLn SIO.stdout $ TE.decodeUtf8 b + err $ "cryptopals: result" + out . TE.decodeUtf8 . B16.encodeBase16' $ b main :: IO () main = do