cryptopals

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

RepeatingKeyXor.hs (1262B)


      1 {-# LANGUAGE OverloadedStrings #-}
      2 {-# LANGUAGE RecordWildCards #-}
      3 
      4 module Main where
      5 
      6 import qualified Cryptopals.Util as CU
      7 import qualified Data.ByteString.Base16 as B16
      8 import qualified Data.Text as T
      9 import qualified Data.Text.Encoding as TE
     10 import qualified Data.Text.IO as TIO
     11 import qualified Options.Applicative as O
     12 
     13 data Encoding =
     14     Utf8
     15   | Utf16
     16 
     17 data Args = Args {
     18     argsKey :: T.Text
     19   , argsInp :: T.Text
     20   , argsEnc :: Encoding
     21   }
     22 
     23 ops :: O.Parser Args
     24 ops = Args
     25   <$> O.argument O.str (O.metavar "KEY")
     26   <*> O.argument O.str (O.metavar "INPUT")
     27   <*> O.flag Utf8 Utf16 (
     28         O.long "hex" <>
     29         O.help "input is hex-encoded"
     30         )
     31 
     32 rxor :: Args -> IO ()
     33 rxor Args {..} = do
     34   let k = TE.encodeUtf8 argsKey
     35       v = case argsEnc of
     36             Utf8  -> pure $ TE.encodeUtf8 argsInp
     37             Utf16 -> B16.decodeBase16 (TE.encodeUtf8 argsInp)
     38 
     39   case v of
     40     Left e  -> error "FIXME"
     41     Right s ->
     42       TIO.putStrLn . TE.decodeUtf8 . B16.encodeBase16' $
     43         CU.repeatingKeyXor k s
     44 
     45 main :: IO ()
     46 main = do
     47   let pars = O.info (O.helper <*> ops) $
     48            O.fullDesc
     49         <> O.progDesc "compute repeating-key-xor KEY on INPUT"
     50         <> O.header "repeating-key-xor"
     51 
     52   args <- O.execParser pars
     53 
     54   rxor args
     55