Skip to content

Commit

Permalink
Implement buffer Xor
Browse files Browse the repository at this point in the history
  • Loading branch information
remusao committed Jun 20, 2017
1 parent d5c16a1 commit fc57248
Show file tree
Hide file tree
Showing 6 changed files with 26 additions and 10 deletions.
1 change: 1 addition & 0 deletions hcryptopals.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ library
hs-source-dirs: src
exposed-modules: Lib
other-modules: Crypto.Pals.Encoding
, Crypto.Pals.Xor
, Crypto.Pals.BitStream
build-depends: base >= 4.7 && < 5
, bytestring
Expand Down
2 changes: 1 addition & 1 deletion src/Crypto/Pals/BitStream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ groupByN n xs =
data BitChunk = BitChunk
{ size :: Int
, getBits :: Word8
} deriving (Show)
} deriving (Show, Eq)

type BitStream = [BitChunk]

Expand Down
2 changes: 1 addition & 1 deletion src/Crypto/Pals/Encoding.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ generateBytesToBitsTable symbols padding = V.generate 127 gen
gen i =
case chr i `elemIndex` symbols of
Just n -> BitChunk padding (fromIntegral n)
Nothing -> BitChunk 0 0
Nothing -> error "This character is not valid for the given encoding"


generateBitsToBytesTable :: String -> VU.Vector Word8
Expand Down
10 changes: 10 additions & 0 deletions src/Crypto/Pals/Xor.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@

module Crypto.Pals.Xor where

import qualified Data.Bits as Bits
import qualified Data.ByteString.Lazy as B

xor :: B.ByteString -> B.ByteString -> Maybe B.ByteString
xor bs1 bs2
| B.length bs1 /= B.length bs2 = Nothing
| otherwise = Just . B.pack . B.zipWith Bits.xor bs1 $ bs2
2 changes: 2 additions & 0 deletions src/Lib.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
module Lib
( module Crypto.Pals.Encoding
, module Crypto.Pals.BitStream
, module Crypto.Pals.Xor
) where

import Crypto.Pals.Encoding
import Crypto.Pals.BitStream
import Crypto.Pals.Xor
19 changes: 11 additions & 8 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ symbolsToWord8 = map (fromIntegral . ord)


forAllB64 = forAll $
Gen.filter (\b64 -> length b64 `mod` 3 == 0) $
Gen.list (Range.linear 1 100) (Gen.element $ symbolsToWord8 b64Symbols)
where
b64Symbols = ['0'..'9'] ++ ['A'..'Z'] ++ ['a'..'z'] ++ ['/', '+']
Expand All @@ -39,24 +40,26 @@ prop_groupByN =
Gen.list (Range.linear 1 100) (Gen.word8 $ Range.linear 0 255)

let bitStream = map (BitChunk 8) words
let groups = map (BitChunk n) $ groupByN n bitStream
toList groups === toList bitStream
let bitStream2 = map (BitChunk n) $ groupByN n bitStream
let bitStream3 = map (BitChunk 8) $ groupByN 8 bitStream2
bitStream === bitStream3
toList bitStream3 === toList bitStream


prop_hex :: Property
prop_hex =
property $ do
hex <- forAllHex
let packed = B.pack hex
packed === (bitsToHex . hexToBits $ packed)
str <- forAllHex
let packed = B.pack str
packed === (unhex . hex $ packed)


prop_base64 :: Property
prop_base64 =
property $ do
b64 <- forAllB64
let packed = B.pack b64
packed === (bitsToB64 . b64ToBits $ packed)
str <- forAllB64
let packed = B.pack str
packed === (unb64 . b64 $ packed)


prop_hex2b64 :: Property
Expand Down

0 comments on commit fc57248

Please sign in to comment.