{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MonoLocalBinds #-} module Tests.Cipher( transformsTo , keyStreamIs , zeros ) where import Raaz.Core import Prelude hiding (length) import Tests.Core.Imports import Tests.Core.Utils import Implementation import Interface transformsTo :: (Format fmt1, Format fmt2, Show (Nounce Prim), Show (Key Prim)) => fmt1 -> fmt2 -> (Key Prim, Nounce Prim, Int) -> Spec transformsTo :: fmt1 -> fmt2 -> (Key Prim, Nounce Prim, Int) -> Spec transformsTo fmt1 inp fmt2 expected (Key Prim key,Nounce Prim nounce,Int ctr) = String -> Expectation -> SpecWith (Arg Expectation) forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) it String msg (Expectation -> SpecWith (Arg Expectation)) -> Expectation -> SpecWith (Arg Expectation) forall a b. (a -> b) -> a -> b $ ByteString result ByteString -> ByteString -> Expectation forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `shouldBe` fmt2 -> ByteString forall fmt. Format fmt => fmt -> ByteString decodeFormat fmt2 expected where result :: ByteString result = Key Prim -> Nounce Prim -> BlockCount Prim -> ByteString -> ByteString encryptAt Key Prim key Nounce Prim nounce (Int -> Proxy Prim -> BlockCount Prim forall p. Int -> Proxy p -> BlockCount p blocksOf Int ctr Proxy Prim forall k (t :: k). Proxy t Proxy) (ByteString -> ByteString) -> ByteString -> ByteString forall a b. (a -> b) -> a -> b $ fmt1 -> ByteString forall fmt. Format fmt => fmt -> ByteString decodeFormat fmt1 inp msg :: String msg = [String] -> String unwords [ (Show (Key Prim), Show (Nounce Prim)) => Key Prim -> Nounce Prim -> Int -> String Key Prim -> Nounce Prim -> Int -> String withKeyNounce Key Prim key Nounce Prim nounce Int ctr , String "encrypts" , String -> String shortened (String -> String) -> String -> String forall a b. (a -> b) -> a -> b $ fmt1 -> String forall a. Show a => a -> String show fmt1 inp , String "to" , String -> String shortened (String -> String) -> String -> String forall a b. (a -> b) -> a -> b $ fmt2 -> String forall a. Show a => a -> String show fmt2 expected ] withKeyNounce :: (Show (Key Prim), Show (Nounce Prim)) => Key Prim -> Nounce Prim -> Int -> String withKeyNounce :: Key Prim -> Nounce Prim -> Int -> String withKeyNounce Key Prim key Nounce Prim nounce Int ctr = [String] -> String unwords [ String "with {" , String "key:" String -> String -> String forall a. [a] -> [a] -> [a] ++ String -> String shortened (Key Prim -> String forall a. Show a => a -> String show Key Prim key) , String ", nounce:" String -> String -> String forall a. [a] -> [a] -> [a] ++ String -> String shortened (Nounce Prim -> String forall a. Show a => a -> String show Nounce Prim nounce) , String ", counter:" String -> String -> String forall a. [a] -> [a] -> [a] ++ Int -> String forall a. Show a => a -> String show Int ctr , String "}" ] keyStreamIs :: ( Show (Key Prim), Show (Nounce Prim), Format fmt) => fmt -> (Key Prim, Nounce Prim, Int) -> Spec keyStreamIs :: fmt -> (Key Prim, Nounce Prim, Int) -> Spec keyStreamIs fmt expected (Key Prim key, Nounce Prim nounce, Int ctr) = String -> Expectation -> SpecWith (Arg Expectation) forall a. (HasCallStack, Example a) => String -> a -> SpecWith (Arg a) it String msg (Expectation -> SpecWith (Arg Expectation)) -> Expectation -> SpecWith (Arg Expectation) forall a b. (a -> b) -> a -> b $ ByteString result ByteString -> ByteString -> Expectation forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `shouldBe` ByteString decoded where decoded :: ByteString decoded = fmt -> ByteString forall fmt. Format fmt => fmt -> ByteString decodeFormat fmt expected result :: ByteString result = Key Prim -> Nounce Prim -> BlockCount Prim -> ByteString -> ByteString encryptAt Key Prim key Nounce Prim nounce (Int -> Proxy Prim -> BlockCount Prim forall p. Int -> Proxy p -> BlockCount p blocksOf Int ctr Proxy Prim forall k (t :: k). Proxy t Proxy) (ByteString -> ByteString) -> ByteString -> ByteString forall a b. (a -> b) -> a -> b $ BYTES Int -> ByteString zeros (BYTES Int -> ByteString) -> BYTES Int -> ByteString forall a b. (a -> b) -> a -> b $ ByteString -> BYTES Int Raaz.Core.length ByteString decoded msg :: String msg = [String] -> String unwords [ (Show (Key Prim), Show (Nounce Prim)) => Key Prim -> Nounce Prim -> Int -> String Key Prim -> Nounce Prim -> Int -> String withKeyNounce Key Prim key Nounce Prim nounce Int ctr , String "key stream is" , String -> String shortened (String -> String) -> String -> String forall a b. (a -> b) -> a -> b $ fmt -> String forall a. Show a => a -> String show fmt expected ] zeros :: BYTES Int -> ByteString zeros :: BYTES Int -> ByteString zeros = WriteTo -> ByteString forall a. Encodable a => a -> ByteString toByteString (WriteTo -> ByteString) -> (BYTES Int -> WriteTo) -> BYTES Int -> ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . BYTES Int -> WriteTo forall u. LengthUnit u => u -> WriteTo writeZero where writeZero :: LengthUnit u => u -> WriteTo writeZero :: u -> WriteTo writeZero = Word8 -> u -> WriteTo forall n. LengthUnit n => Word8 -> n -> WriteTo writeBytes Word8 0