Skip to content

Instantly share code, notes, and snippets.

@supki
Created July 7, 2012 15:29
Show Gist options
  • Save supki/3066888 to your computer and use it in GitHub Desktop.
Save supki/3066888 to your computer and use it in GitHub Desktop.
Cryptography coursera class exercise #2.
{-# LANGUAGE UnicodeSyntax #-}
import Control.Applicative ((<$>))
import Control.Monad ((<=<))
import Crypto.Cipher.AES (Key, IV(..), decryptCBC, decryptCTR, initKey)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
main ∷ IO ()
main = do
mapM_ (print <=< cbc "data/key1.dat") ["data/ciphertext1.dat", "data/ciphertext2.dat"]
mapM_ (print <=< ctr "data/key2.dat") ["data/ciphertext3.dat", "data/ciphertext4.dat"]
where
cbc = decryptWith decryptCBC
ctr = decryptWith decryptCTR
decryptWith ∷ (Key → IV → ByteString → ByteString) → FilePath → FilePath → IO ByteString
decryptWith f keyfp datafp =
do key ← initKey <$> B.readFile keyfp
(iv, cipher) ← parse <$> B.readFile datafp
return $ f key iv cipher
parse ∷ ByteString → (IV, ByteString)
parse bs = (IV iv, cipher)
where
(iv, cipher) = B.splitAt 16 bs
@supki
Copy link
Author

supki commented Jul 7, 2012

% runhaskell Main.hs
"Basic CBC mode encryption needs padding.\b\b\b\b\b\b\b\b"
"Our implementation uses rand. IV\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE\DLE"
"CTR mode lets you build a stream cipher from a block cipher."
"Always avoid the two time pad!"

@dmalikov
Copy link

dmalikov commented Jul 7, 2012

SPOILER ATTACK

@junwei-wang
Copy link

what the fuck

@korniltsev
Copy link

dislike

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment