cardano-crypto-class-2.2.0.0: Type classes abstracting over cryptography primitives for Cardano
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Crypto.KES.Class

Description

Abstract key evolving signatures.

Synopsis

KES algorithm class

class (Typeable v, Show (VerKeyKES v), Eq (VerKeyKES v), Show (SigKES v), Eq (SigKES v), NoThunks (SigKES v), NoThunks (SignKeyKES v), NoThunks (VerKeyKES v), KnownNat (SeedSizeKES v), KnownNat (SizeVerKeyKES v), KnownNat (SizeSignKeyKES v), KnownNat (SizeSigKES v)) ⇒ KESAlgorithm v where Source #

Associated Types

data VerKeyKES v ∷ Type Source #

data SigKES v ∷ Type Source #

data SignKeyKES v ∷ Type Source #

type SeedSizeKES v ∷ Nat Source #

type SizeVerKeyKES v ∷ Nat Source #

type SizeSignKeyKES v ∷ Nat Source #

type SizeSigKES v ∷ Nat Source #

type ContextKES v ∷ Type Source #

Context required to run the KES algorithm

Unit by default (no context required)

type ContextKES v = ()

type Signable v ∷ TypeConstraint Source #

type Signable v = Empty

Methods

algorithmNameKES ∷ proxy v → String Source #

hashVerKeyKESHashAlgorithm h ⇒ VerKeyKES v → Hash h (VerKeyKES v) Source #

verifyKES Source #

Arguments

∷ (Signable v a, HasCallStack) 
ContextKES v 
VerKeyKES v 
Period

The current period for the key

→ a 
SigKES v 
Either String () 

Full KES verification. This method checks that the signature itself checks out (as per verifySigKES), and also makes sure that it matches the provided VerKey.

totalPeriodsKES ∷ proxy v → Word Source #

Return the total number of KES periods supported by this algorithm. The KES algorithm is assumed to support a fixed maximum number of periods, not a variable number.

Do note that this is the total number of periods not the total number of evolutions. The difference is off-by-one. For example if there are 2 periods (period 0 and 1) then there is only one evolution.

rawSerialiseVerKeyKESVerKeyKES v → ByteString Source #

rawSerialiseSigKESSigKES v → ByteString Source #

rawDeserialiseVerKeyKESByteStringMaybe (VerKeyKES v) Source #

rawDeserialiseSigKESByteStringMaybe (SigKES v) Source #

deriveVerKeyKES ∷ (MonadST m, MonadThrow m) ⇒ SignKeyKES v → m (VerKeyKES v) Source #

signKES Source #

Arguments

∷ ∀ a m. (Signable v a, MonadST m, MonadThrow m) 
ContextKES v 
Period

The current period for the key

→ a 
SignKeyKES v 
→ m (SigKES v) 

updateKESWith Source #

Arguments

∷ (MonadST m, MonadThrow m) 
MLockedAllocator m 
ContextKES v 
SignKeyKES v 
Period

The current period for the key, not the target period.

→ m (Maybe (SignKeyKES v)) 

genKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → MLockedSeed (SeedSizeKES v) → m (SignKeyKES v) Source #

forgetSignKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → SignKeyKES v → m () Source #

Forget a signing key synchronously, rather than waiting for GC. In some non-mock instances this provides a guarantee that the signing key is no longer in memory.

The precondition is that this key value will not be used again.

Instances

Instances details
KESAlgorithm NeverKES Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

(DSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) ⇒ KESAlgorithm (CompactSingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

algorithmNameKES ∷ proxy (CompactSingleKES d) → String Source #

hashVerKeyKESHashAlgorithm h ⇒ VerKeyKES (CompactSingleKES d) → Hash h (VerKeyKES (CompactSingleKES d)) Source #

verifyKES ∷ (Signable (CompactSingleKES d) a, HasCallStack) ⇒ ContextKES (CompactSingleKES d) → VerKeyKES (CompactSingleKES d) → Period → a → SigKES (CompactSingleKES d) → Either String () Source #

totalPeriodsKES ∷ proxy (CompactSingleKES d) → Word Source #

rawSerialiseVerKeyKESVerKeyKES (CompactSingleKES d) → ByteString Source #

rawSerialiseSigKESSigKES (CompactSingleKES d) → ByteString Source #

rawDeserialiseVerKeyKESByteStringMaybe (VerKeyKES (CompactSingleKES d)) Source #

rawDeserialiseSigKESByteStringMaybe (SigKES (CompactSingleKES d)) Source #

deriveVerKeyKES ∷ (MonadST m, MonadThrow m) ⇒ SignKeyKES (CompactSingleKES d) → m (VerKeyKES (CompactSingleKES d)) Source #

signKES ∷ (Signable (CompactSingleKES d) a, MonadST m, MonadThrow m) ⇒ ContextKES (CompactSingleKES d) → Period → a → SignKeyKES (CompactSingleKES d) → m (SigKES (CompactSingleKES d)) Source #

updateKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → ContextKES (CompactSingleKES d) → SignKeyKES (CompactSingleKES d) → Period → m (Maybe (SignKeyKES (CompactSingleKES d))) Source #

genKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → MLockedSeed (SeedSizeKES (CompactSingleKES d)) → m (SignKeyKES (CompactSingleKES d)) Source #

forgetSignKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → SignKeyKES (CompactSingleKES d) → m () Source #

KnownNat t ⇒ KESAlgorithm (MockKES t) Source #

Mock key evolving signatures.

What is the difference between Mock KES and Simple KES (Cardano.Crypto.KES.Simple), you may ask? Simple KES satisfies the outward appearance of a KES scheme through assembling a pre-generated list of keys and iterating through them. Mock KES, on the other hand, pretends to be KES but in fact does no key evolution whatsoever.

Simple KES is appropriate for testing, since it will for example reject old keys. Mock KES is more suitable for a basic testnet, since it doesn't suffer from the performance implications of shuffling a giant list of keys around

Instance details

Defined in Cardano.Crypto.KES.Mock

DSIGNMAlgorithm d ⇒ KESAlgorithm (SingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

(OptimizedKESAlgorithm d, SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d, NoThunks (VerKeyKES (CompactSumKES h d)), KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) ⇒ KESAlgorithm (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

algorithmNameKES ∷ proxy (CompactSumKES h d) → String Source #

hashVerKeyKESHashAlgorithm h0 ⇒ VerKeyKES (CompactSumKES h d) → Hash h0 (VerKeyKES (CompactSumKES h d)) Source #

verifyKES ∷ (Signable (CompactSumKES h d) a, HasCallStack) ⇒ ContextKES (CompactSumKES h d) → VerKeyKES (CompactSumKES h d) → Period → a → SigKES (CompactSumKES h d) → Either String () Source #

totalPeriodsKES ∷ proxy (CompactSumKES h d) → Word Source #

rawSerialiseVerKeyKESVerKeyKES (CompactSumKES h d) → ByteString Source #

rawSerialiseSigKESSigKES (CompactSumKES h d) → ByteString Source #

rawDeserialiseVerKeyKESByteStringMaybe (VerKeyKES (CompactSumKES h d)) Source #

rawDeserialiseSigKESByteStringMaybe (SigKES (CompactSumKES h d)) Source #

deriveVerKeyKES ∷ (MonadST m, MonadThrow m) ⇒ SignKeyKES (CompactSumKES h d) → m (VerKeyKES (CompactSumKES h d)) Source #

signKES ∷ (Signable (CompactSumKES h d) a, MonadST m, MonadThrow m) ⇒ ContextKES (CompactSumKES h d) → Period → a → SignKeyKES (CompactSumKES h d) → m (SigKES (CompactSumKES h d)) Source #

updateKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → ContextKES (CompactSumKES h d) → SignKeyKES (CompactSumKES h d) → Period → m (Maybe (SignKeyKES (CompactSumKES h d))) Source #

genKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → MLockedSeed (SeedSizeKES (CompactSumKES h d)) → m (SignKeyKES (CompactSumKES h d)) Source #

forgetSignKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → SignKeyKES (CompactSumKES h d) → m () Source #

(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) ⇒ KESAlgorithm (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

algorithmNameKES ∷ proxy (SimpleKES d t) → String Source #

hashVerKeyKESHashAlgorithm h ⇒ VerKeyKES (SimpleKES d t) → Hash h (VerKeyKES (SimpleKES d t)) Source #

verifyKES ∷ (Signable (SimpleKES d t) a, HasCallStack) ⇒ ContextKES (SimpleKES d t) → VerKeyKES (SimpleKES d t) → Period → a → SigKES (SimpleKES d t) → Either String () Source #

totalPeriodsKES ∷ proxy (SimpleKES d t) → Word Source #

rawSerialiseVerKeyKESVerKeyKES (SimpleKES d t) → ByteString Source #

rawSerialiseSigKESSigKES (SimpleKES d t) → ByteString Source #

rawDeserialiseVerKeyKESByteStringMaybe (VerKeyKES (SimpleKES d t)) Source #

rawDeserialiseSigKESByteStringMaybe (SigKES (SimpleKES d t)) Source #

deriveVerKeyKES ∷ (MonadST m, MonadThrow m) ⇒ SignKeyKES (SimpleKES d t) → m (VerKeyKES (SimpleKES d t)) Source #

signKES ∷ (Signable (SimpleKES d t) a, MonadST m, MonadThrow m) ⇒ ContextKES (SimpleKES d t) → Period → a → SignKeyKES (SimpleKES d t) → m (SigKES (SimpleKES d t)) Source #

updateKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → ContextKES (SimpleKES d t) → SignKeyKES (SimpleKES d t) → Period → m (Maybe (SignKeyKES (SimpleKES d t))) Source #

genKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → MLockedSeed (SeedSizeKES (SimpleKES d t)) → m (SignKeyKES (SimpleKES d t)) Source #

forgetSignKeyKESWith ∷ (MonadST m, MonadThrow m) ⇒ MLockedAllocator m → SignKeyKES (SimpleKES d t) → m () Source #

(KESAlgorithm d, SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d, KnownNat ((SizeSignKeyKES d + SeedSizeKES d) + (2 * SizeVerKeyKES d)), KnownNat (SizeSigKES d + (SizeVerKeyKES d * 2))) ⇒ KESAlgorithm (SumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Associated Types

data VerKeyKES (SumKES h d) Source #

data SigKES (SumKES h d) Source #

data SignKeyKES (SumKES h d) Source #

type SeedSizeKES (SumKES h d) ∷ Nat Source #

type SizeVerKeyKES (SumKES h d) ∷ Nat Source #

type SizeSignKeyKES (SumKES h d) ∷ Nat Source #

type SizeSigKES (SumKES h d) ∷ Nat Source #

type ContextKES (SumKES h d) Source #

type Signable (SumKES h d) ∷ TypeConstraint Source #

genKeyKES ∷ ∀ v m. (KESAlgorithm v, MonadST m, MonadThrow m) ⇒ MLockedSeed (SeedSizeKES v) → m (SignKeyKES v) Source #

Key generation

updateKES Source #

Arguments

∷ ∀ v m. (KESAlgorithm v, MonadST m, MonadThrow m) 
ContextKES v 
SignKeyKES v 
Period

The current period for the key, not the target period.

→ m (Maybe (SignKeyKES v)) 

Update the KES signature key to the next period, given the current period.

It returns Nothing if the cannot be evolved any further.

The precondition (to get a Just result) is that the current KES period of the input key is not the last period. The given period must be the current KES period of the input key (not the next or target).

The postcondition is that in case a key is returned, its current KES period is incremented by one compared to before.

Note that you must track the current period separately, and to skip to a later period requires repeated use of this function, since it only increments one period at once.

forgetSignKeyKES ∷ (KESAlgorithm v, MonadST m, MonadThrow m) ⇒ SignKeyKES v → m () Source #

Forget a signing key synchronously, rather than waiting for GC. In some non-mock instances this provides a guarantee that the signing key is no longer in memory.

The precondition is that this key value will not be used again.

type Period = Word Source #

The KES period. Periods are enumerated from zero.

Be careful of fencepost errors: if there are 2 periods (period 0 and 1) then there is only one key evolution.

class KESAlgorithm v ⇒ OptimizedKESAlgorithm v where Source #

Subclass for KES algorithms that embed a copy of the VerKey into the signature itself, rather than relying on the externally supplied VerKey alone. Some optimizations made in the CompactSingleKES and CompactSumKES implementations require this additional interface in order to avoid redundant computations.

Methods

verifySigKES Source #

Arguments

∷ (Signable v a, HasCallStack) 
ContextKES v 
Period

The current period for the key

→ a 
SigKES v 
Either String () 

Partial verification: this method only verifies the signature itself, but it does not check it against any externally-provided VerKey. Use verifyKES for full KES verification.

verKeyFromSigKESContextKES v → PeriodSigKES v → VerKeyKES v Source #

Extract a VerKey from a SigKES. Note that a VerKey embedded in or derived from a SigKES is effectively user-supplied, so it is not enough to validate a SigKES against this VerKey (like verifySigKES does); you must also compare the VerKey against an externally-provided key that you want to verify against (see verifyKES).

SignKeyWithPeriodKES wrapper

data SignKeyWithPeriodKES v Source #

A sign key bundled with its associated period.

Instances

Instances details
Generic (SignKeyWithPeriodKES v) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

Associated Types

type Rep (SignKeyWithPeriodKES v) ∷ TypeType Source #

(KESAlgorithm v, Show (SignKeyKES v)) ⇒ Show (SignKeyWithPeriodKES v) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

(KESAlgorithm v, Eq (SignKeyKES v)) ⇒ Eq (SignKeyWithPeriodKES v) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

KESAlgorithm v ⇒ NoThunks (SignKeyWithPeriodKES v) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

type Rep (SignKeyWithPeriodKES v) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

type Rep (SignKeyWithPeriodKES v) = D1 ('MetaData "SignKeyWithPeriodKES" "Cardano.Crypto.KES.Class" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "SignKeyWithPeriodKES" 'PrefixI 'True) (S1 ('MetaSel ('Just "skWithoutPeriodKES") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyKES v)) :*: S1 ('MetaSel ('Just "periodKES") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Period)))

SignedKES wrapper

newtype SignedKES v a Source #

Constructors

SignedKES 

Fields

Instances

Instances details
Generic (SignedKES v a) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

Associated Types

type Rep (SignedKES v a) ∷ TypeType Source #

Methods

fromSignedKES v a → Rep (SignedKES v a) x Source #

toRep (SignedKES v a) x → SignedKES v a Source #

KESAlgorithm v ⇒ Show (SignedKES v a) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

Methods

showsPrecIntSignedKES v a → ShowS Source #

showSignedKES v a → String Source #

showList ∷ [SignedKES v a] → ShowS Source #

KESAlgorithm v ⇒ Eq (SignedKES v a) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

Methods

(==)SignedKES v a → SignedKES v a → Bool Source #

(/=)SignedKES v a → SignedKES v a → Bool Source #

KESAlgorithm v ⇒ NoThunks (SignedKES v a) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

type Rep (SignedKES v a) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

type Rep (SignedKES v a) = D1 ('MetaData "SignedKES" "Cardano.Crypto.KES.Class" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "SignedKES" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SigKES v))))

signedKES ∷ (KESAlgorithm v, Signable v a, MonadST m, MonadThrow m) ⇒ ContextKES v → Period → a → SignKeyKES v → m (SignedKES v a) Source #

verifySignedKES ∷ (KESAlgorithm v, Signable v a) ⇒ ContextKES v → VerKeyKES v → Period → a → SignedKES v a → Either String () Source #

CBOR encoding and decoding

decodeSigKES ∷ ∀ v s. KESAlgorithm v ⇒ Decoder s (SigKES v) Source #

Encoded Size expressions

encodedVerKeyKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (VerKeyKES v) → Size Source #

Size expression for VerKeyKES which is using sizeVerKeyKES encoded as Size.

encodedSignKeyKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (SignKeyKES v) → Size Source #

Size expression for SignKeyKES which is using sizeSignKeyKES encoded as Size.

encodedSigKESSizeExpr ∷ ∀ v. KESAlgorithm v ⇒ Proxy (SigKES v) → Size Source #

Size expression for SigKES which is using sizeSigKES encoded as Size.

Raw sizes

sizeVerKeyKES ∷ ∀ v proxy. KESAlgorithm v ⇒ proxy v → Word Source #

sizeSigKES ∷ ∀ v proxy. KESAlgorithm v ⇒ proxy v → Word Source #

sizeSignKeyKES ∷ ∀ v proxy. KESAlgorithm v ⇒ proxy v → Word Source #

seedSizeKES ∷ ∀ v proxy. KESAlgorithm v ⇒ proxy v → Word Source #

The upper bound on the Seed size needed by genKeyKES

Unsound APIs

class KESAlgorithm v ⇒ UnsoundKESAlgorithm v where Source #

Unsound operations on KES sign keys. These operations violate secure forgetting constraints by leaking secrets to unprotected memory. Consider using the DirectSerialise / DirectDeserialise APIs instead.

Instances

Instances details
UnsoundKESAlgorithm NeverKES Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

(KESAlgorithm (CompactSingleKES d), UnsoundDSIGNMAlgorithm d) ⇒ UnsoundKESAlgorithm (CompactSingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KnownNat t ⇒ UnsoundKESAlgorithm (MockKES t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

(KESAlgorithm (SingleKES d), UnsoundDSIGNMAlgorithm d) ⇒ UnsoundKESAlgorithm (SingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm (CompactSumKES h d), UnsoundKESAlgorithm d) ⇒ UnsoundKESAlgorithm (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

(UnsoundDSIGNMAlgorithm d, KnownNat t, KESAlgorithm (SimpleKES d t)) ⇒ UnsoundKESAlgorithm (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

(KESAlgorithm (SumKES h d), UnsoundKESAlgorithm d) ⇒ UnsoundKESAlgorithm (SumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

class KESAlgorithm v ⇒ UnsoundPureKESAlgorithm v where Source #

Pure implementations of the core KES operations. These are unsound, because proper handling of KES secrets (seeds, sign keys) requires mlocking and deterministic erasure ("secure forgetting"), which is not possible in pure code. This API is only provided for testing purposes; it must not be used to generate or use real KES keys.

Associated Types

data UnsoundPureSignKeyKES v ∷ Type Source #

Instances

Instances details
UnsoundPureKESAlgorithm NeverKES Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

data UnsoundPureSignKeyKES NeverKES Source #

(KESAlgorithm (CompactSingleKES d), UnsoundDSIGNMAlgorithm d) ⇒ UnsoundPureKESAlgorithm (CompactSingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KnownNat t ⇒ UnsoundPureKESAlgorithm (MockKES t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Associated Types

data UnsoundPureSignKeyKES (MockKES t) Source #

(KESAlgorithm (SingleKES d), UnsoundDSIGNMAlgorithm d) ⇒ UnsoundPureKESAlgorithm (SingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Associated Types

data UnsoundPureSignKeyKES (SingleKES d) Source #

(KESAlgorithm (CompactSumKES h d), HashAlgorithm h, UnsoundPureKESAlgorithm d) ⇒ UnsoundPureKESAlgorithm (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

data UnsoundPureSignKeyKES (CompactSumKES h d) Source #

(KESAlgorithm (SimpleKES d t), KnownNat t, DSIGNAlgorithm d, UnsoundDSIGNMAlgorithm d) ⇒ UnsoundPureKESAlgorithm (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

data UnsoundPureSignKeyKES (SimpleKES d t) Source #

(KESAlgorithm (SumKES h d), HashAlgorithm h, UnsoundPureKESAlgorithm d) ⇒ UnsoundPureKESAlgorithm (SumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Associated Types

data UnsoundPureSignKeyKES (SumKES h d) Source #

Utility functions

unsoundPureSignKeyKESToSoundSignKeyKESViaSer ∷ (MonadST m, MonadThrow m, UnsoundKESAlgorithm k, UnsoundPureKESAlgorithm k) ⇒ UnsoundPureSignKeyKES k → m (SignKeyKES k) Source #

Helper function for implementing unsoundPureSignKeyKESToSoundSignKeyKES for KES algorithms that support both UnsoundKESAlgorithm and UnsoundPureKESAlgorithm. For such KES algorithms, unsound sign keys can be marshalled to sound sign keys by serializing and then deserializing them.