Skip to content

Instantly share code, notes, and snippets.

@KWMalik
Forked from supki/Main.hs
Created July 30, 2012 20:03
Show Gist options
  • Save KWMalik/3209697 to your computer and use it in GitHub Desktop.
Save KWMalik/3209697 to your computer and use it in GitHub Desktop.
Cryptography coursera class exercise #1.
{-# LANGUAGE UnicodeSyntax #-}
module Main where
import Control.Applicative ((<$>))
import Control.Monad (forM_, when)
import Control.Monad.State (execState, modify)
import Data.Bits (Bits, xor)
import Data.Char (chr, isAlpha)
import Data.List (maximumBy, group, sort, zip4)
import Data.List.Split (splitEvery)
import Data.IntMap (IntMap)
import Data.Ord (comparing)
import qualified Data.IntMap as M
-- | Read ciphers from "ciphers.txt", try to guess a key and decrypt secret message
main ∷ IO ()
main = do
ciphers ← readCiphers "ciphers.txt"
let key = M.elems $ chooseMostFrequent $ distribution $ combineWith xor ciphers
mapM_ (putStrLn . map chr . zipWith xor key) ciphers
-- | Read routine
readCiphers ∷ Read α ⇒ FilePath → IO [[α]]
readCiphers fp = map readCipher . lines <$> readFile fp
where readCipher = map (read . ("0x" ++)) . splitEvery 2
-- | Get all xored ciphers pairs
combineWith ∷ (α → α → β) → [[α]] → [([α], [α], [β])]
combineWith f cs = [ (a,b,zipWith f a b) | a ← cs, b ← cs ]
-- | Construct frequency IntMap
distribution ∷ Bits α ⇒ [([α], [α], [Int])] → IntMap [α]
distribution xs = flip execState (M.empty) $
forM_ xs $ \(as,bs,cs) →
forM_ (zip4 [0..] as bs cs) $ \(i,a,b,c) → do
let hui = M.insertWith (++) i $ map (xor 32) [a, b]
when (isAlpha $ chr c) $ modify hui
-- | NOTE: head is safe here since there is no empty lists
-- while construction distribution IntMap
chooseMostFrequent ∷ (Eq α, Ord α) ⇒ IntMap [α] → IntMap α
chooseMostFrequent = M.map (head . maximumBy (comparing length) . group . sort)
@KWMalik
Copy link
Author

KWMalik commented Jul 30, 2012

% runhaskell Main.hs
Plaintext 1: We can factor the number 15 with quantum computers. We can also factor the number 1
Plaintext 2: Euler would probably enjoy that now his theorem becomes a corner stone of crypto -
Plaintext 3: The nice thing about Keeyloq is now we cryptographers can drive a lot of fancy cars
Plaintext 4: The ciphertext produced by a weak encryption algorithm looks as good as ciphertext
Plaintext 5: You don't want to buy a set of car keys from a guy who specializes in stealing cars
Plaintext 6: There are two types of cryptography - that which will keep secrets safe from your l
Plaintext 7: There are two types of cyptography: one that allows the Government to use brute for
Plaintext 8: We can see the point where the chip is unhappy if a wrong bit is sent and consumes
Plaintext 9: A (private-key) encryption scheme states 3 algorithms, namely a procedure for gene
Plaintext 10: The Concise OxfordDictionary (2006) defines crypto as the art of writing for sol
Target Plaintext : The secret message is: When using a stream cipher, never use the key more than once

@transparentdata243
Copy link

Does Prof. Dan Boneh allow students to post homework solutions?

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