| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Cardano.Crypto.KES.Class
Description
Abstract key evolving signatures.
Synopsis
- class (Typeable v, Show (VerKeyKES v), Eq (VerKeyKES v), Show (SignKeyKES v), Show (SigKES v), Eq (SigKES v), NoThunks (SigKES v), NoThunks (SignKeyKES v), NoThunks (VerKeyKES v), KnownNat (SeedSizeKES v)) => KESAlgorithm v where
- type SeedSizeKES v :: Nat
 - data VerKeyKES v :: Type
 - data SignKeyKES v :: Type
 - data SigKES v :: Type
 - type ContextKES v :: Type
 - type Signable v :: Type -> Constraint
 - algorithmNameKES :: proxy v -> String
 - deriveVerKeyKES :: SignKeyKES v -> VerKeyKES v
 - hashVerKeyKES :: HashAlgorithm h => VerKeyKES v -> Hash h (VerKeyKES v)
 - signKES :: (Signable v a, HasCallStack) => ContextKES v -> Period -> a -> SignKeyKES v -> SigKES v
 - verifyKES :: (Signable v a, HasCallStack) => ContextKES v -> VerKeyKES v -> Period -> a -> SigKES v -> Either String ()
 - updateKES :: HasCallStack => ContextKES v -> SignKeyKES v -> Period -> Maybe (SignKeyKES v)
 - totalPeriodsKES :: proxy v -> Word
 - genKeyKES :: Seed -> SignKeyKES v
 - seedSizeKES :: proxy v -> Word
 - forgetSignKeyKES :: SignKeyKES v -> IO ()
 - sizeVerKeyKES :: proxy v -> Word
 - sizeSignKeyKES :: proxy v -> Word
 - sizeSigKES :: proxy v -> Word
 - rawSerialiseVerKeyKES :: VerKeyKES v -> ByteString
 - rawSerialiseSignKeyKES :: SignKeyKES v -> ByteString
 - rawSerialiseSigKES :: SigKES v -> ByteString
 - rawDeserialiseVerKeyKES :: ByteString -> Maybe (VerKeyKES v)
 - rawDeserialiseSignKeyKES :: ByteString -> Maybe (SignKeyKES v)
 - rawDeserialiseSigKES :: ByteString -> Maybe (SigKES v)
 
 - type Period = Word
 - class KESAlgorithm v => OptimizedKESAlgorithm v where
- verifySigKES :: (Signable v a, HasCallStack) => ContextKES v -> Period -> a -> SigKES v -> Either String ()
 - verKeyFromSigKES :: ContextKES v -> Period -> SigKES v -> VerKeyKES v
 
 - verifyOptimizedKES :: (OptimizedKESAlgorithm v, Signable v a, HasCallStack) => ContextKES v -> VerKeyKES v -> Period -> a -> SigKES v -> Either String ()
 - newtype SignedKES v a = SignedKES {}
 - signedKES :: (KESAlgorithm v, Signable v a) => ContextKES v -> Period -> a -> SignKeyKES v -> SignedKES v a
 - verifySignedKES :: (KESAlgorithm v, Signable v a) => ContextKES v -> VerKeyKES v -> Period -> a -> SignedKES v a -> Either String ()
 - encodeVerKeyKES :: KESAlgorithm v => VerKeyKES v -> Encoding
 - decodeVerKeyKES :: forall v s. KESAlgorithm v => Decoder s (VerKeyKES v)
 - encodeSignKeyKES :: KESAlgorithm v => SignKeyKES v -> Encoding
 - decodeSignKeyKES :: forall v s. KESAlgorithm v => Decoder s (SignKeyKES v)
 - encodeSigKES :: KESAlgorithm v => SigKES v -> Encoding
 - decodeSigKES :: forall v s. KESAlgorithm v => Decoder s (SigKES v)
 - encodeSignedKES :: KESAlgorithm v => SignedKES v a -> Encoding
 - decodeSignedKES :: KESAlgorithm v => Decoder s (SignedKES v a)
 - encodedVerKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (VerKeyKES v) -> Size
 - encodedSignKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SignKeyKES v) -> Size
 - encodedSigKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SigKES v) -> Size
 - hashPairOfVKeys :: (KESAlgorithm d, HashAlgorithm h) => (VerKeyKES d, VerKeyKES d) -> Hash h (VerKeyKES d, VerKeyKES d)
 - zeroSeed :: KESAlgorithm d => Proxy d -> Seed
 - mungeName :: String -> String
 
KES algorithm class
class (Typeable v, Show (VerKeyKES v), Eq (VerKeyKES v), Show (SignKeyKES v), Show (SigKES v), Eq (SigKES v), NoThunks (SigKES v), NoThunks (SignKeyKES v), NoThunks (VerKeyKES v), KnownNat (SeedSizeKES v)) => KESAlgorithm v where Source #
Minimal complete definition
algorithmNameKES, deriveVerKeyKES, signKES, verifyKES, updateKES, totalPeriodsKES, genKeyKES, sizeVerKeyKES, sizeSignKeyKES, sizeSigKES, rawSerialiseVerKeyKES, rawSerialiseSignKeyKES, rawSerialiseSigKES, rawDeserialiseVerKeyKES, rawDeserialiseSignKeyKES, rawDeserialiseSigKES
Associated Types
type SeedSizeKES v :: Nat Source #
data VerKeyKES v :: Type Source #
data SignKeyKES v :: Type Source #
data SigKES v :: Type 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 :: Type -> Constraint Source #
Methods
algorithmNameKES :: proxy v -> String Source #
deriveVerKeyKES :: SignKeyKES v -> VerKeyKES v Source #
hashVerKeyKES :: HashAlgorithm h => VerKeyKES v -> Hash h (VerKeyKES v) Source #
Arguments
| :: (Signable v a, HasCallStack) | |
| => ContextKES v | |
| -> Period | The current period for the key  | 
| -> a | |
| -> SignKeyKES v | |
| -> SigKES v | 
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.
Arguments
| :: HasCallStack | |
| => ContextKES v | |
| -> SignKeyKES v | |
| -> Period | The current period for the key, not the target period.  | 
| -> 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.
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.
genKeyKES :: Seed -> SignKeyKES v Source #
seedSizeKES :: proxy v -> Word Source #
forgetSignKeyKES :: SignKeyKES v -> IO () 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.
sizeVerKeyKES :: proxy v -> Word Source #
sizeSignKeyKES :: proxy v -> Word Source #
sizeSigKES :: proxy v -> Word Source #
rawSerialiseVerKeyKES :: VerKeyKES v -> ByteString Source #
rawSerialiseSignKeyKES :: SignKeyKES v -> ByteString Source #
rawSerialiseSigKES :: SigKES v -> ByteString Source #
rawDeserialiseVerKeyKES :: ByteString -> Maybe (VerKeyKES v) Source #
rawDeserialiseSignKeyKES :: ByteString -> Maybe (SignKeyKES v) Source #
rawDeserialiseSigKES :: ByteString -> Maybe (SigKES v) Source #
Instances
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
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.
verKeyFromSigKES :: ContextKES v -> Period -> SigKES 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).
Instances
| (KESAlgorithm (CompactSingleKES d), DSIGNAlgorithm d) => OptimizedKESAlgorithm (CompactSingleKES d) Source # | |
Defined in Cardano.Crypto.KES.CompactSingle Methods verifySigKES :: (Signable (CompactSingleKES d) a, HasCallStack) => ContextKES (CompactSingleKES d) -> Period -> a -> SigKES (CompactSingleKES d) -> Either String () Source # verKeyFromSigKES :: ContextKES (CompactSingleKES d) -> Period -> SigKES (CompactSingleKES d) -> VerKeyKES (CompactSingleKES d) Source #  | |
| (KESAlgorithm (CompactSumKES h d), OptimizedKESAlgorithm d, HashAlgorithm h) => OptimizedKESAlgorithm (CompactSumKES h d) Source # | |
Defined in Cardano.Crypto.KES.CompactSum Methods verifySigKES :: (Signable (CompactSumKES h d) a, HasCallStack) => ContextKES (CompactSumKES h d) -> Period -> a -> SigKES (CompactSumKES h d) -> Either String () Source # verKeyFromSigKES :: ContextKES (CompactSumKES h d) -> Period -> SigKES (CompactSumKES h d) -> VerKeyKES (CompactSumKES h d) Source #  | |
verifyOptimizedKES :: (OptimizedKESAlgorithm v, Signable v a, HasCallStack) => ContextKES v -> VerKeyKES v -> Period -> a -> SigKES v -> Either String () Source #
SignedKES wrapper
signedKES :: (KESAlgorithm v, Signable v a) => ContextKES v -> Period -> a -> SignKeyKES v -> 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
encodeVerKeyKES :: KESAlgorithm v => VerKeyKES v -> Encoding Source #
decodeVerKeyKES :: forall v s. KESAlgorithm v => Decoder s (VerKeyKES v) Source #
encodeSignKeyKES :: KESAlgorithm v => SignKeyKES v -> Encoding Source #
decodeSignKeyKES :: forall v s. KESAlgorithm v => Decoder s (SignKeyKES v) Source #
encodeSigKES :: KESAlgorithm v => SigKES v -> Encoding Source #
decodeSigKES :: forall v s. KESAlgorithm v => Decoder s (SigKES v) Source #
encodeSignedKES :: KESAlgorithm v => SignedKES v a -> Encoding Source #
decodeSignedKES :: KESAlgorithm v => Decoder s (SignedKES v a) Source #
Encoded Size expressions
encodedVerKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (VerKeyKES v) -> Size Source #
Size expression for VerKeyKES which is using sizeVerKeyKES encoded
 as Size.
encodedSignKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SignKeyKES v) -> Size Source #
Size expression for SignKeyKES which is using sizeSignKeyKES encoded
 as Size.
encodedSigKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SigKES v) -> Size Source #
Size expression for SigKES which is using sizeSigKES encoded as
 Size.
Utility functions
hashPairOfVKeys :: (KESAlgorithm d, HashAlgorithm h) => (VerKeyKES d, VerKeyKES d) -> Hash h (VerKeyKES d, VerKeyKES d) Source #