Skip to content
Snippets Groups Projects
Commit 9aaabbec authored by Jean-Paul Calderone's avatar Jean-Paul Calderone
Browse files

Merge remote-tracking branch 'origin/main' into 5.decoding-and-decryption

parents 8d4203de 3045b8d4
No related branches found
No related tags found
1 merge request!7Implement enough encryption and encoding to be able to read plaintext from Tahoe-LAFS-generated SDMF shares
-- | Expose the library's public interface.
module Tahoe.SDMF (
Share (..),
Writer (..),
Reader (..),
encode,
decode,
module Tahoe.SDMF.Internal.Share,
module Tahoe.SDMF.Internal.Capability,
module Tahoe.SDMF.Internal.Encoding,
) where
import Tahoe.SDMF.Internal.Capability
import Tahoe.SDMF.Internal.Encoding
import Tahoe.SDMF.Internal.Share
import Tahoe.SDMF.Internal.Capability (
Reader (..),
Writer (..),
)
import Tahoe.SDMF.Internal.Encoding (
decode,
encode,
)
import Tahoe.SDMF.Internal.Share (
Reader (..),
Share (..),
Writer (..),
)
-- | Structured representations of SDMF capabilities.
module Tahoe.SDMF.Internal.Capability where
import Crypto.Cipher.AES128 (AESKey128)
import Crypto.Classes (buildKey)
import Crypto.Types (IV)
import Prelude hiding (Read)
import qualified Data.ByteString as B
import Data.Serialize (encode)
import Tahoe.CHK.Crypto (taggedHash, taggedPairHash)
import Tahoe.SDMF.Internal.Keys (Read, Write)
-- | A read capability for an SDMF object.
data Reader = Reader
{ readerReadKey :: B.ByteString
{ readerReadKey :: Read
, readerVerificationKeyHash :: B.ByteString
}
deriving (Show)
-- | A write capability for an SDMF object.
data Writer = Writer
{ writerWriteKey :: AESKey128
{ writerWriteKey :: Write
, writerReader :: Reader
}
deriveReader :: AESKey128 -> B.ByteString -> Reader
deriveReader writeKey readerVerificationKeyHash = Reader{..}
where
readerReadKey = taggedHash readKeyLength mutableReadKeyTag (encode writeKey)
readKeyLength :: Int
readKeyLength = 32
mutableReadKeyTag :: B.ByteString
mutableReadKeyTag = "allmydata_mutable_writekey_to_readkey_v1"
{- | Compute the encryption (and decryption) key used to convert the
application payload plaintext to ciphertext and back again.
-}
deriveEncryptionKey :: MonadFail m => Reader -> IV AESKey128 -> m AESKey128
deriveEncryptionKey Reader{readerReadKey} iv = do
let k = buildKey $ taggedPairHash encryptionKeyLength mutableDataKeyTag readerReadKey (encode iv)
case k of
Nothing -> fail "Could not build AESKey128 when deriving encryption key"
Just key -> pure key
mutableDataKeyTag :: B.ByteString
mutableDataKeyTag = "allmydata_mutable_readkey_to_datakey_v1"
encryptionKeyLength :: Int
encryptionKeyLength = 16
deriving (Show)
......@@ -34,10 +34,15 @@ newtype Signature = Signature {unSignature :: RSA.PrivateKey}
deriving newtype (Eq, Show)
data Write = Write {unWrite :: AES128, writeKeyBytes :: ByteArray.ScrubbedBytes}
instance Show Write where
show (Write _ bs) = T.unpack $ T.concat ["<WriteKey ", encodeBase32Unpadded (ByteArray.convert bs), ">"]
data Read = Read {unRead :: AES128, readKeyBytes :: ByteArray.ScrubbedBytes}
instance Show Read where
show (Read _ bs) = T.unpack $ T.concat ["<ReadKey ", encodeBase32Unpadded (ByteArray.convert bs), ">"]
newtype StorageIndex = StorageIndex {unStorageIndex :: B.ByteString}
newtype WriteEnablerMaster = WriteEnablerMaster ByteArray.ScrubbedBytes
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment