cryptopals

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

FixedXor.hs (1347B)


      1 {-# LANGUAGE OverloadedStrings #-}
      2 {-# LANGUAGE RecordWildCards #-}
      3 
      4 module Main where
      5 
      6 import qualified Cryptopals.Util as CU
      7 import qualified Data.ByteString as BS
      8 import qualified Data.ByteString.Base16 as B16
      9 import qualified Data.Text as T
     10 import qualified Data.Text.Encoding as TE
     11 import qualified Data.Text.IO as TIO
     12 import qualified Options.Applicative as O
     13 import qualified System.Exit as SE
     14 import qualified System.IO as SIO
     15 
     16 data Args = Args {
     17     argsKey :: T.Text
     18   , argsInp :: T.Text
     19   }
     20 
     21 ops :: O.Parser Args
     22 ops = Args
     23   <$> O.argument O.str (O.metavar "KEY")
     24   <*> O.argument O.str (O.metavar "INPUT")
     25 
     26 fxor :: Args -> IO ()
     27 fxor Args {..} = do
     28   let args = do
     29         k <- B16.decodeBase16 $ TE.encodeUtf8 argsKey
     30         v <- B16.decodeBase16 $ TE.encodeUtf8 argsInp
     31         if   BS.length k /= BS.length v
     32         then Left "fixed-xor: unequal-length inputs"
     33         else pure (k, v)
     34 
     35   case args of
     36     Left e -> do
     37       TIO.hPutStrLn SIO.stderr ("cryptopals: " <> e)
     38       SE.exitFailure
     39 
     40     Right (k, v) -> do
     41       let res = CU.fixedXor k v
     42       TIO.putStrLn . TE.decodeUtf8 . B16.encodeBase16' $ res
     43 
     44 main :: IO ()
     45 main = do
     46   let pars = O.info (O.helper <*> ops) $
     47            O.fullDesc
     48         <> O.progDesc "compute fixed-xor KEY on INPUT"
     49         <> O.header "fixed-xor"
     50 
     51   args <- O.execParser pars
     52 
     53   fxor args
     54