tahoe-ssk-0.3.0.0: An implementation of the Tahoe-LAFS SSK cryptographic protocols
Safe HaskellNone
LanguageHaskell2010

Tahoe.SDMF.Internal.Keys

Description

Key types, derivations, and related functionality for SDMF.

See docsspecificationsmutable.rst for details.

Synopsis

Documentation

newtype KeyPair Source #

Constructors

KeyPair 

Instances

Instances details
Show KeyPair Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

newtype Verification Source #

Constructors

Verification 

Instances

Instances details
Eq Verification Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Show Verification Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

newtype Signature Source #

Constructors

Signature 

Instances

Instances details
Eq Signature Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Show Signature Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

data Write Source #

Constructors

Write 

Instances

Instances details
Eq Write Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

(==) :: Write -> Write -> Bool #

(/=) :: Write -> Write -> Bool #

Show Write Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

showsPrec :: Int -> Write -> ShowS #

show :: Write -> String #

showList :: [Write] -> ShowS #

Binary Write Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

put :: Write -> Put #

get :: Get Write #

putList :: [Write] -> Put #

data Read Source #

Constructors

Read 

Instances

Instances details
Eq Read Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

(==) :: Read -> Read -> Bool #

(/=) :: Read -> Read -> Bool #

Show Read Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

showsPrec :: Int -> Read -> ShowS #

show :: Read -> String #

showList :: [Read] -> ShowS #

Binary Read Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

put :: Read -> Put #

get :: Get Read #

putList :: [Read] -> Put #

data Data Source #

Constructors

Data 

Instances

Instances details
Eq Data Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

(==) :: Data -> Data -> Bool #

(/=) :: Data -> Data -> Bool #

Show Data Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

showsPrec :: Int -> Data -> ShowS #

show :: Data -> String #

showList :: [Data] -> ShowS #

Binary Data Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

put :: Data -> Put #

get :: Get Data #

putList :: [Data] -> Put #

newtype SDMF_IV Source #

Constructors

SDMF_IV (IV AES128) 

Instances

Instances details
Eq SDMF_IV Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

(==) :: SDMF_IV -> SDMF_IV -> Bool #

(/=) :: SDMF_IV -> SDMF_IV -> Bool #

Show SDMF_IV Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

ByteArrayAccess SDMF_IV Source # 
Instance details

Defined in Tahoe.SDMF.Internal.Keys

Methods

length :: SDMF_IV -> Int #

withByteArray :: SDMF_IV -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: SDMF_IV -> Ptr p -> IO () #

keyPairBits :: Int Source #

The size of the public/private key pair to generate.

keyLength :: Int Source #

The number of bytes in the block cipher key.

newKeyPair :: MonadRandom m => m KeyPair Source #

Create a new, random key pair (publicprivate aka verificationsignature) of the appropriate type and size for SDMF encryption.

deriveWriteKey :: Signature -> Maybe Write Source #

Compute the write key for a given signature key for an SDMF share.

deriveReadKey :: Write -> Maybe Read Source #

Compute the read key for a given write key for an SDMF share.

deriveDataKey :: SDMF_IV -> Read -> Maybe Data Source #

Compute the data encryption/decryption key for a given read key for an SDMF share.

deriveStorageIndex :: Read -> StorageIndex Source #

Compute the storage index for a given read key for an SDMF share.

deriveWriteEnablerMaster :: Write -> WriteEnablerMaster Source #

Derive the "write enabler master" secret for a given write key for an SDMF share.

deriveWriteEnabler :: ByteString -> WriteEnablerMaster -> WriteEnabler Source #

Derive the "write enabler" secret for a given peer and "write enabler master" for an SDMF share.

deriveVerificationHash :: Verification -> ByteString Source #

Compute the verification key hash of the given verification key for inclusion in an SDMF share.

mutableVerificationKeyHashTag :: ByteString Source #

The tag used when hashing the verification key to the verification key hash for inclusion in SDMF shares.

verificationKeyToBytes :: Verification -> ByteString Source #

Encode a public key to the Tahoe-LAFS canonical bytes representation - X.509 SubjectPublicKeyInfo of the ASN.1 DER serialization of an RSA PublicKey.

signatureKeyToBytes :: Signature -> ByteString Source #

Encode a private key to the Tahoe-LAFS canonical bytes representation - X.509 SubjectPublicKeyInfo of the ASN.1 DER serialization of an RSA PublicKey.

signatureKeyFromBytes :: ByteString -> Either String Signature Source #

Decode a private key from the Tahoe-LAFS canonical bytes representation.

encryptSignatureKey :: Write -> Signature -> ByteString Source #

Encrypt the signature key for inclusion in the SDMF share itself.

shorten :: Int -> Text -> Text Source #

Replace most of the tail of a string with a short placeholder. If the string is not much longer than n then the result might not actually be shorter.

TODO: Deduplicate this between here and tahoe-chk.