diff --git a/ChangeLog.md b/ChangeLog.md index 7a8e5ec6df60bdd4d257c1ccbfc185177e35f6cb..90cda79116e9d0b433f4f47ccfe4a946b98b2f0e 100644 --- a/ChangeLog.md +++ b/ChangeLog.md @@ -22,6 +22,10 @@ Most of these changes are to (exposed) implementation details rather than the primary high-level interface and should not impact most applications. +* The `cereal`, `cipher-aes128`, `crypto-api`, `tagged`, and `monad-loop` + direct dependencies have been dropped. `cryptonite` (already a dependency) + is now used for AES128 operations. + ## 0.1.0.2 * `taggedPairHash` now respects the size parameter passed to it. diff --git a/src/Tahoe/CHK.hs b/src/Tahoe/CHK.hs index 434f0dee9104a9a579111673128ec2529bea0be1..f6d5f71aa30110cd7b0af08217896876e555fa4c 100644 --- a/src/Tahoe/CHK.hs +++ b/src/Tahoe/CHK.hs @@ -73,9 +73,7 @@ module Tahoe.CHK ( import qualified Codec.FEC as ZFEC import Control.Applicative (Alternative (empty)) import Control.Lens (view) -import Crypto.Cipher.AES128 ( - AESKey128, - ) +import Crypto.Cipher.AES (AES128) import Crypto.Hash ( Context, HashAlgorithm, @@ -93,6 +91,7 @@ import Data.List.Extra (snoc) import Data.Maybe (fromJust, mapMaybe) import Data.Word (Word64) import qualified Tahoe.CHK.Capability as Cap +import Tahoe.CHK.Cipher (Key) import Tahoe.CHK.Crypto ( blockHash', ciphertextSegmentHash', @@ -293,7 +292,7 @@ padCiphertext requiredShares bs -} encode :: -- | The encryption/decryption key. - AESKey128 -> + Key AES128 -> -- | The ZFEC parameters for this encoding. This determines how many shares -- will come out of this function. Parameters -> diff --git a/src/Tahoe/CHK/Capability.hs b/src/Tahoe/CHK/Capability.hs index b2fa06893d0c6186adaa42d5e54673c856db159d..a0bc62b07b107e43f23b958bd79b3d3be1d9099e 100644 --- a/src/Tahoe/CHK/Capability.hs +++ b/src/Tahoe/CHK/Capability.hs @@ -2,6 +2,7 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeApplications #-} module Tahoe.CHK.Capability ( CHK (..), @@ -23,15 +24,12 @@ module Tahoe.CHK.Capability ( import Control.Lens (view) import Control.Lens.TH (makeLenses) -import Crypto.Cipher.AES128 ( - AESKey128, - ) -import Crypto.Classes (buildKey) +import Crypto.Cipher.AES (AES128) +import Crypto.Cipher.Types (Cipher (cipherInit)) +import Crypto.Error (maybeCryptoError) +import Data.ByteArray (convert) import qualified Data.ByteString as B import qualified Data.ByteString.Base32 as B -import Data.Serialize ( - encode, - ) import qualified Data.Set as Set import qualified Data.Text as T import qualified Data.Text.Encoding as T @@ -39,6 +37,7 @@ import Data.TreeDiff.Class (ToExpr (..)) import Data.Void (Void) import Data.Word (Word16, Word64) import GHC.Generics (Generic) +import Tahoe.CHK.Cipher (Key (..)) import Tahoe.CHK.Crypto (storageIndexHash) import qualified Tahoe.CHK.Parsing import Text.Megaparsec (ErrorFancy (ErrorFail), Parsec, count, fancyFailure, oneOf, try, (<|>)) @@ -138,7 +137,7 @@ data Reader = Reader -- key to turn the original plaintext into ciphertext and back again. The -- read key is also used to derive the verify key for the verify -- capability. See ``storageIndexHash``. - _readKey :: AESKey128 + _readKey :: Key AES128 , -- | The verify capability for this read capability. _verifier :: Verifier } @@ -169,7 +168,7 @@ instance Show Reader where ":" [ "URI" , "CHK" - , shorten 4 . showBase32 . encode $ view readKey reader + , shorten 4 . showBase32 . convert . keyBytes $ view readKey reader , shorten 4 . showBase32 $ view (verifier . fingerprint) reader , showT $ view (verifier . required) reader , showT $ view (verifier . total) reader @@ -179,7 +178,7 @@ instance Show Reader where -- Construct a key with Eq and Ord instances for the Reader Eq and Ord -- instances. readerKey :: Reader -> (B.ByteString, Verifier) -readerKey r = (encode $ view readKey r, view verifier r) +readerKey r = (convert $ view readKey r, view verifier r) {- | A "Content-Hash-Key" (CHK) capability is small value that can be used to perform some operation on a (usually) larger value that may be stored @@ -215,7 +214,7 @@ dangerRealShow (CHKReader r) = ":" [ "URI" , "CHK" - , showBase32 . encode $ view readKey r + , showBase32 . convert $ view readKey r , showBase32 $ view (verifier . fingerprint) r , showT $ view (verifier . required) r , showT $ view (verifier . total) r @@ -248,7 +247,7 @@ pReader = makeReader <$> ( string "URI:CHK:" *> pBase32 rfc3548Alphabet 128 - >>= maybe (fancyFailure . Set.singleton . ErrorFail . T.unpack $ "Failed to build AESKey128 from CHK read key bytes") pure . buildKey + >>= maybe (fancyFailure . Set.singleton . ErrorFail . T.unpack $ "Failed to build AESKey128 from CHK read key bytes") pure . maybeCryptoError . cipherInit ) <* char ':' <*> pBase32 rfc3548Alphabet 256 @@ -262,7 +261,7 @@ pReader = {- | Construct a CHK read capability from its components. This includes the correct derivation of the corresponding CHK verify capability. -} -makeReader :: AESKey128 -> B.ByteString -> Word16 -> Word16 -> Integer -> Reader +makeReader :: Key AES128 -> B.ByteString -> Word16 -> Word16 -> Integer -> Reader makeReader readKey' fingerprint' required' total' size' = Reader readKey' (deriveVerifier readKey' fingerprint' required' total' size') @@ -271,7 +270,7 @@ makeReader readKey' fingerprint' required' total' size' = -} deriveVerifier :: -- | The read key - AESKey128 -> + Key AES128 -> -- | The fingerprint B.ByteString -> -- | The required number of shares diff --git a/src/Tahoe/CHK/Cipher.hs b/src/Tahoe/CHK/Cipher.hs new file mode 100644 index 0000000000000000000000000000000000000000..953c6fa18a79c1115054f81dfc01582d9cfaa0ee --- /dev/null +++ b/src/Tahoe/CHK/Cipher.hs @@ -0,0 +1,53 @@ +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} + +module Tahoe.CHK.Cipher ( + Key (keyBytes, keyCipher), +) where + +import Control.DeepSeq (NFData) +import Crypto.Cipher.Types (AEAD, BlockCipher (..), Cipher (..)) +import Data.ByteArray (ScrubbedBytes) +import qualified Data.ByteArray as BA +import Data.Coerce (coerce) +import GHC.Generics (Generic) + +{- | A block cipher key which can be deserialized from or serialized to a + ByteArray. + + This is a wrapper around Crypto.Cipher.Types.Cipher which does not provide a + way to recover the original bytes of the key. We provide this by keeping the + original bytes around. +-} +data Key cipher = Key {keyBytes :: ScrubbedBytes, keyCipher :: cipher} + +deriving instance Generic (Key cipher) +deriving instance NFData cipher => NFData (Key cipher) + +instance forall cipher. Cipher cipher => Cipher (Key cipher) where + cipherInit bs = Key (BA.convert bs) <$> cipherInit bs + cipherName _ = cipherName @cipher undefined + cipherKeySize _ = cipherKeySize @cipher undefined + +instance forall cipher. BlockCipher cipher => BlockCipher (Key cipher) where + blockSize _ = blockSize @cipher undefined + ecbEncrypt = ecbEncrypt . keyCipher + ecbDecrypt = ecbDecrypt . keyCipher + cbcEncrypt (Key _ cipher) iv = cbcEncrypt cipher (coerce iv) + cbcDecrypt (Key _ cipher) iv = cbcDecrypt cipher (coerce iv) + + cfbEncrypt (Key _ cipher) iv = cfbEncrypt cipher (coerce iv) + cfbDecrypt (Key _ cipher) iv = cfbDecrypt cipher (coerce iv) + ctrCombine (Key _ cipher) iv = ctrCombine cipher (coerce iv) + + aeadInit mode (Key _ cipher) iv = wrap <$> aeadInit mode cipher iv + where + wrap = coerce @(AEAD cipher) @(AEAD (Key cipher)) + +instance BA.ByteArrayAccess (Key cipher) where + length (Key ba _) = BA.length ba + withByteArray (Key ba _) = BA.withByteArray ba diff --git a/src/Tahoe/CHK/Crypto.hs b/src/Tahoe/CHK/Crypto.hs index f994f4770e09673fb1f0b30771663bb688fcf6b2..e4c727bd3b51c645d2646fac42d091741340b6f7 100644 --- a/src/Tahoe/CHK/Crypto.hs +++ b/src/Tahoe/CHK/Crypto.hs @@ -25,10 +25,6 @@ module Tahoe.CHK.Crypto ( import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL -import Data.Serialize ( - encode, - ) - import Crypto.Hash ( Digest, HashAlgorithm, @@ -36,29 +32,25 @@ import Crypto.Hash ( hashDigestSize, hashlazy, ) -import Crypto.Types (ByteLength) +import Data.ByteArray (convert) +import Crypto.Cipher.AES (AES128) import Crypto.Hash.Algorithms ( SHA1, SHA256 (SHA256), ) -import Crypto.Cipher.AES128 ( - AESKey128, - ) - -import Tahoe.Netstring ( - netstring, - ) - +import Tahoe.CHK.Cipher (Key) +import Tahoe.CHK.SHA256d (Digest' (..), SHA256d, toBytes) +import Tahoe.CHK.Types (Parameters (Parameters), StorageIndex) import Tahoe.CHK.URIExtension ( URIExtension, showBytes, uriExtensionToBytes, ) - -import Tahoe.CHK.SHA256d (Digest' (..), SHA256d, toBytes) -import Tahoe.CHK.Types (Parameters (Parameters), StorageIndex) +import Tahoe.Netstring ( + netstring, + ) sha1 :: B.ByteString -> B.ByteString sha1 xs = toBytes (hash xs :: Digest SHA1) @@ -106,8 +98,8 @@ storageIndexTag = "allmydata_immutable_key_to_storage_index_v1" -- Compute the storage index for a given encryption key -- allmydata.util.hashutil.storage_index_hash -storageIndexHash :: AESKey128 -> StorageIndex -storageIndexHash = taggedHash storageIndexLength storageIndexTag . encode +storageIndexHash :: Key AES128 -> StorageIndex +storageIndexHash = taggedHash storageIndexLength storageIndexTag . convert ciphertextTag :: B.ByteString ciphertextTag = "allmydata_crypttext_v1" @@ -158,6 +150,8 @@ convergenceEncryptionHashLazy secret params bytes = tag = BL.fromStrict . netstring $ convergenceEncryptionTag secret params +type ByteLength = Int + convergenceSecretLength :: ByteLength convergenceSecretLength = 16 diff --git a/src/Tahoe/CHK/Encrypt.hs b/src/Tahoe/CHK/Encrypt.hs index 787903b336341ffc4566d6d021f1ada1af741d30..de9c796045a7782ee457497fd0cf275366ce6705 100644 --- a/src/Tahoe/CHK/Encrypt.hs +++ b/src/Tahoe/CHK/Encrypt.hs @@ -1,18 +1,33 @@ -- | Support the encryption requirements of CHK. -module Tahoe.CHK.Encrypt (encrypt, decrypt) where +module Tahoe.CHK.Encrypt (encrypt, encryptLazy, decrypt, decryptLazy) where -import Crypto.Cipher.AES128 (AESKey128, BlockCipher (ctrLazy), zeroIV) -import qualified Data.ByteString.Lazy as LB +import Crypto.Cipher.Types (BlockCipher (ctrCombine), nullIV) +import Data.ByteArray (ByteArray) +import qualified Data.ByteString.Lazy as LBS -{- | AES128-CTR encrypt a byte string in the manner used by CHK. +{- | CTR-mode encrypt a byte string using some block cipher. + + When used for CHKv1 or CHKv2 the block cipher should be AES128. This replaces allmydata.immutable.upload.EncryptAnUploadable The only noteworthy piece here is that encryption starts with the zero IV. -} -encrypt :: AESKey128 -> LB.ByteString -> LB.ByteString -encrypt key plaintext = fst $ ctrLazy key zeroIV plaintext +encrypt :: (BlockCipher cipher, ByteArray ba) => cipher -> ba -> ba +encrypt key = ctrCombine key nullIV + +{- | Like encrypt but operate on lazy bytestrings. TODO: Make this more + efficient than converting to/from strict ByteString! +-} +encryptLazy :: BlockCipher cipher => cipher -> LBS.ByteString -> LBS.ByteString +encryptLazy cipher lbs = LBS.fromStrict (encrypt cipher (LBS.toStrict lbs)) -- | AES128-CTR decrypt a byte string in the manner used by CHK. -decrypt :: AESKey128 -> LB.ByteString -> LB.ByteString +decrypt :: (BlockCipher cipher, ByteArray ba) => cipher -> ba -> ba decrypt = encrypt + +{- | Like decrypt but operate on lazy bytestrings. TODO: Make this more + efficient than converting to/from strict ByteString! +-} +decryptLazy :: BlockCipher cipher => cipher -> LBS.ByteString -> LBS.ByteString +decryptLazy = encryptLazy diff --git a/src/Tahoe/CHK/Upload.hs b/src/Tahoe/CHK/Upload.hs index 56cd72f97f2eed3eb9b19d4e7946a603ad19ad35..0db1afc00b2e09c155f4e35b53aa5dda8c7bc199 100644 --- a/src/Tahoe/CHK/Upload.hs +++ b/src/Tahoe/CHK/Upload.hs @@ -1,4 +1,6 @@ +{-# LANGUAGE PackageImports #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} module Tahoe.CHK.Upload ( UploadResult (uploadResultReadCap, uploadResultExistingShares, uploadResultShareMap), @@ -34,6 +36,7 @@ import Data.IORef ( ) import qualified Data.Binary as Binary +import Data.ByteArray (ScrubbedBytes) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL @@ -48,11 +51,6 @@ import qualified Data.Set as Set import qualified Data.Map.Strict as Map -import Crypto.Classes ( - buildKey, - buildKeyIO, - ) - import qualified Tahoe.CHK.Capability as Cap import System.IO ( @@ -63,10 +61,11 @@ import System.IO ( openFile, ) -import Crypto.Cipher.AES128 ( - AESKey128, - ) +import Crypto.Cipher.AES (AES128) +import Crypto.Cipher.Types (BlockCipher, Cipher (cipherInit, cipherKeySize), KeySizeSpecifier (..)) +import "cryptonite" Crypto.Random (getRandomBytes) +import Tahoe.CHK.Cipher (Key) import Tahoe.CHK.Crypto ( convergenceEncryptionHashLazy, storageIndexHash, @@ -85,15 +84,16 @@ import Tahoe.CHK.Types ( import Tahoe.Util (nextMultipleOf) +import Crypto.Error (maybeCryptoError) import Data.Tuple.Extra (thd3) import Tahoe.CHK ( encode, ) -import Tahoe.CHK.Encrypt (encrypt) +import Tahoe.CHK.Encrypt (encryptLazy) -- Some data that can be uploaded. data Uploadable = Uploadable - { uploadableKey :: AESKey128 + { uploadableKey :: Key AES128 , uploadableSize :: Size , uploadableParameters :: Parameters , uploadableReadCleartext :: Integer -> IO B.ByteString @@ -189,7 +189,7 @@ encryptAndEncode :: IO ([BL.ByteString], Cap.Reader) encryptAndEncode (Uploadable readKey _ params read') = do plaintext <- readAll read' - let ciphertext = encrypt readKey plaintext + let ciphertext = encryptLazy readKey plaintext (shares, cap) <- encode readKey params ciphertext pure (map Binary.encode shares, cap) where @@ -210,7 +210,7 @@ upload :: -- | The servers to consider uploading shares to. [StorageServer] -> -- | The encryption key (to derive the storage index). - AESKey128 -> + Key AES128 -> -- | The encoding parameters (XXX only for happy, right?) Parameters -> -- | The share data to upload. @@ -278,7 +278,7 @@ adjustSegmentSize (Parameters segmentSize total happy required) dataSize = nextMultipleOf required . min segmentSize -- Create an uploadable with the given key. -filesystemUploadable :: AESKey128 -> FilePath -> Parameters -> IO Uploadable +filesystemUploadable :: Key AES128 -> FilePath -> Parameters -> IO Uploadable filesystemUploadable key path params = do fhandle <- openBinaryFile path ReadMode fsize <- hFileSize fhandle @@ -315,7 +315,7 @@ memoryUploadableWithConvergence secret size content params = let key = getConvergentKey secret (adjustSegmentSize params size) content in memoryUploadable key size content params -memoryUploadable :: AESKey128 -> Integer -> BL.ByteString -> Parameters -> IO Uploadable +memoryUploadable :: Key AES128 -> Integer -> BL.ByteString -> Parameters -> IO Uploadable memoryUploadable key size content params = let makeReader :: BL.ByteString -> IO (Integer -> IO BL.ByteString) makeReader allContent = @@ -335,14 +335,25 @@ memoryUploadable key size content params = } -- allmydata.immutable.upload.FileHandle._get_encryption_key_convergent -getConvergentKey :: B.ByteString -> Parameters -> BL.ByteString -> AESKey128 +getConvergentKey :: B.ByteString -> Parameters -> BL.ByteString -> Key AES128 getConvergentKey secret params content = - fromJust . buildKey $ convergenceEncryptionHashLazy secret params content + fromJust . maybeCryptoError . cipherInit $ convergenceEncryptionHashLazy secret params content + +buildKeyIO :: forall cipher. BlockCipher cipher => IO (Key cipher) +buildKeyIO = do + keyBytes <- getRandomBytes @IO @ScrubbedBytes keySize + pure . fromJust . maybeCryptoError . cipherInit $ keyBytes + where + keySize = case cipherKeySize @cipher undefined of + KeySizeRange _ high -> high + KeySizeEnum [] -> error "no key sizes!" + KeySizeEnum (s : _) -> s + KeySizeFixed s -> s -- Create an uploadable with a random key. filesystemUploadableRandomConvergence :: FilePath -> Parameters -> IO Uploadable filesystemUploadableRandomConvergence path params = do - key <- buildKeyIO :: IO AESKey128 + key <- buildKeyIO :: IO (Key AES128) filesystemUploadable key path params prettyFormatSharemap :: ShareMap -> Text diff --git a/tahoe-chk.cabal b/tahoe-chk.cabal index 570d1785376ae3693009c7a2b005564239f3ddad..383af07df5aece4189e7c5c03ac3a1578681aab9 100644 --- a/tahoe-chk.cabal +++ b/tahoe-chk.cabal @@ -31,6 +31,7 @@ library exposed-modules: Tahoe.CHK Tahoe.CHK.Capability + Tahoe.CHK.Cipher Tahoe.CHK.Crypto Tahoe.CHK.Encrypt Tahoe.CHK.Merkle @@ -58,12 +59,10 @@ library , base64-bytestring >=1.0.0.3 && <1.3 , binary >=0.8.6 && <0.9 , bytestring >=0.10.8.2 && <0.11 - , cereal >=0.5.8.1 && <0.6 - , cipher-aes128 >=0.7.0.5 && <0.8 , concurrency >=1.11 && <2 , containers >=0.6.0.1 && <0.7 - , crypto-api >=0.13.3 && <0.14 , cryptonite >=0.27 && <0.30 + , deepseq , directory >=1.3.3 && <1.4 , extra >=1.7.7 && <1.8 , fec >=0.1.1 && <0.2 @@ -71,11 +70,9 @@ library , lens >=5.0 && <5.3 , megaparsec >=8.0 && <9.3 , memory >=0.15 && <0.17 - , monad-loops >=0.4.3 && <0.5 , network-byte-order >=0.1.5 && <0.2 , parser-combinators >=1.2.1 && <1.4 , primitive >=0.7.0.1 && <0.8 - , tagged >=0.8.6 && <0.9 , text >=1.2.3.1 && <1.3 , tree-diff >=0.1 && <0.3 , utility-ht >=0.0.15 && <0.1 @@ -127,10 +124,7 @@ test-suite tahoe-chk-tests , base64-bytestring >=1.0.0.3 && <1.3 , binary >=0.8.6 && <0.9 , bytestring >=0.10.8.2 && <0.11 - , cereal >=0.5.8.1 && <0.6 - , cipher-aes128 >=0.7.0.5 && <0.8 , containers >=0.6.0.1 && <0.7 - , crypto-api >=0.13.3 && <0.14 , cryptonite >=0.27 && <0.30 , directory >=1.3.3 && <1.4 , fec >=0.1.1 && <0.2 @@ -140,7 +134,6 @@ test-suite tahoe-chk-tests , megaparsec >=8.0 && <9.3 , memory >=0.15 && <0.17 , scientific >=0.3.6.2 && <0.4 - , tagged >=0.8.6 && <0.9 , tahoe-chk , tasty >=1.2.3 && <1.5 , tasty-hedgehog >=1.0.0.2 && <1.2 diff --git a/test/SpecCHK.hs b/test/SpecCHK.hs index 157e32c158f3cb613184e8e01a0ba6d2e60a8549..066ca15534a27f44e5fadbd5d1cbabca004361e8 100644 --- a/test/SpecCHK.hs +++ b/test/SpecCHK.hs @@ -11,13 +11,9 @@ import Control.Arrow ( ) import Control.Lens (view) import Control.Monad.IO.Class (MonadIO (liftIO)) -import Crypto.Cipher.AES128 ( - AESKey128, - ) -import Crypto.Classes ( - encode, - ) +import Crypto.Cipher.AES (AES128) import qualified Data.Binary as Binary +import Data.ByteArray (convert) import qualified Data.ByteString as B import qualified Data.ByteString.Base64 as Base64 import qualified Data.ByteString.Lazy as BL @@ -54,8 +50,9 @@ import qualified Hedgehog.Range as Range import Tahoe.CHK (padCiphertext) import qualified Tahoe.CHK (decode, encode, segmentCiphertext) import Tahoe.CHK.Capability (Reader, dangerRealShow, pCapability, pReader, verifier) +import Tahoe.CHK.Cipher (Key) import Tahoe.CHK.Crypto (ciphertextSegmentHash', convergenceSecretLength) -import Tahoe.CHK.Encrypt (encrypt) +import Tahoe.CHK.Encrypt (encryptLazy) import Tahoe.CHK.Share ( Share ( _blockSize @@ -112,7 +109,7 @@ import Vectors ( A hard-coded convergence secret is used for simplicity and reproducibility. -} makeValidShares :: Parameters -> BL.ByteString -> IO ([Share], Reader) -makeValidShares params plaintext = Tahoe.CHK.encode key params (encrypt key plaintext) +makeValidShares params plaintext = Tahoe.CHK.encode key params (encryptLazy key plaintext) where key = getConvergentKey "secret" params plaintext @@ -245,7 +242,7 @@ wellKnownCase :: WellKnown -> Assertion wellKnownCase WellKnown{..} = do uploadable <- memoryUploadableWithConvergence wellKnownConvergenceSecret (fromIntegral $ BL.length wellKnownPlaintext) wellKnownPlaintext wellKnownParameters - let ciphertext = encrypt (uploadableKey uploadable) wellKnownPlaintext + let ciphertext = encryptLazy (uploadableKey uploadable) wellKnownPlaintext (shares', cap) <- Tahoe.CHK.encode (uploadableKey uploadable) wellKnownParameters ciphertext let allValid = replicate (fromIntegral $ paramTotalShares wellKnownParameters) True @@ -331,7 +328,7 @@ testEncrypt = assertEqual "expected convergence key" "oBcuR/wKdCgCV2GKKXqiNg==" - (Base64.encode $ encode convergenceKey) + (Base64.encode $ convert convergenceKey) let b64ciphertext = Base64.encode (BL.toStrict ciphertext) assertEqual "known result" knownCorrect b64ciphertext ] @@ -345,9 +342,9 @@ testEncrypt = plaintext = "hello world" ciphertext :: BL.ByteString - ciphertext = encrypt convergenceKey plaintext + ciphertext = encryptLazy convergenceKey plaintext - convergenceKey :: AESKey128 + convergenceKey :: Key AES128 convergenceKey = getConvergentKey convergenceSecret params plaintext convergenceSecret = B.replicate convergenceSecretLength 0x42 diff --git a/test/SpecCrypto.hs b/test/SpecCrypto.hs index 0b07b6b0ef5d5ff5d5882f84f28fd9647a8aa57d..09f9366b61eabec69480945e23ae23e712fe0122 100644 --- a/test/SpecCrypto.hs +++ b/test/SpecCrypto.hs @@ -5,19 +5,14 @@ module SpecCrypto ( tests, ) where -import Crypto.Cipher.AES128 ( - AESKey128, - ) -import Crypto.Classes ( - buildKey, - keyLength, - ) -import Crypto.Types (ByteLength) +import Crypto.Cipher.AES (AES128) +import Crypto.Cipher.Types (Cipher (..), KeySizeSpecifier (..)) +import Crypto.Error (CryptoFailable (CryptoPassed)) import qualified Data.ByteString as B import Data.Char ( ord, ) -import Data.Tagged (Tagged, untag) +import Tahoe.CHK.Cipher (Key) import Tahoe.CHK.Crypto ( blockHash', ciphertextSegmentHash', @@ -64,7 +59,7 @@ tests = -- Adapted from allmydata.test.test_hashutil.HashUtilTests.test_known_answers assertEqual "known value" - (Just "\xb5\x4c\x60\xc5\xb1\x26\x46\xf0\x77\x0\xc4\x4c\x8b\x75\xb9\x48") + (CryptoPassed "\xb5\x4c\x60\xc5\xb1\x26\x46\xf0\x77\x0\xc4\x4c\x8b\x75\xb9\x48") (storageIndexHash <$> xKey) , testCase "tagged hash length" $ do -- The length of the result equals the given size. @@ -129,4 +124,10 @@ tests = ] ] where - xKey = buildKey (B.replicate (untag (keyLength :: Tagged AESKey128 ByteLength)) . fromIntegral . ord $ 'x') :: Maybe AESKey128 + xKey = cipherInit keyBytes :: CryptoFailable (Key AES128) + keyBytes = B.replicate keySize (fromIntegral $ ord 'x') + keySize = case cipherKeySize @(Key AES128) undefined of + KeySizeRange _ high -> high + KeySizeEnum [] -> error "no key sizes!" + KeySizeEnum (s : _) -> s + KeySizeFixed s -> s diff --git a/test/SpecUpload.hs b/test/SpecUpload.hs index 056ddfac229a7b9d8b414ce7f266f105556292d5..74606a751e36f28a17b7fcedd6114dda94b15614 100644 --- a/test/SpecUpload.hs +++ b/test/SpecUpload.hs @@ -2,13 +2,11 @@ module SpecUpload ( tests, ) where +import Data.ByteArray (convert) import Data.ByteString.Base32 ( encodeBase32Unpadded, ) import Data.Maybe (mapMaybe) -import Data.Serialize ( - encode, - ) import Test.Tasty ( TestTree, @@ -153,7 +151,7 @@ testConvergence = assertEqual "The key matches the known correct result" expectedKeyBytes - (encodeBase32Unpadded . encode $ key) + (encodeBase32Unpadded . convert $ key) where key = getConvergentKey secret params (BL.fromStrict dataContent)