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

Cardano.Crypto.KES.CompactSum

Description

A key evolving signatures implementation.

It is a naive recursive implementation of the sum composition from section 3.1 of the "MMM" paper:

Composition and Efficiency Tradeoffs for Forward-Secure Digital Signatures By Tal Malkin, Daniele Micciancio and Sara Miner https://eprint.iacr.org/2001/034

Specfically we do the binary sum composition directly as in the paper, and then use that in a nested/recursive fashion to construct a 7-level deep binary tree version.

This relies on Cardano.Crypto.KES.CompactSingle for the base case.

Compared to the implementation in Sum, this flavor stores only one VerKey in the branch node.

Consider the following Merkle tree:

      (A)
     /   
  (B)     (C)
         
(D) (E) (F) (G)
     ^
 0   1   2   3

The caret points at leaf node E, indicating that the current period is 1. The signatures for leaf nodes D through G all contain their respective DSIGN keys; the signature for branch node B however only holds the signature for node E, and the VerKey for node D. It can reconstruct its own VerKey from these two. The signature for branch node A (the root node), then, only contains the VerKey for node C, and the signature for node B. In other words, the number of individual hashes to be stored equals the depth of the Merkle tree. Compare that to the older, naive SumKES, where each branch node stores two VerKeys: here, the number of keys to store is the depth of the tree times two.

Note that when we verify such a signature, we need to also compare the ultimate VerKey at the root against the one passed in externally, because all VerKeys until that point have been derived from the (user-supplied, so untrusted) signature. But we only need to do this once, at the tree root, so we split up the verification into two parts: verifying a signature against its embedded VerKey, and comparing that VerKey against the externally supplied target key.

NOTE - some functions in this module have been deliberately marked NOINLINE; this is necessary to avoid an edge case in GHC that causes the simplifier to go haywire, leading to a Simplifier ticks exhausted error and very long compilation times. Worse yet, this error will only appear when compiling code that depends on this module, not when compiling the module itself.

Synopsis

Documentation

data CompactSumKES h d Source #

A composition of two KES schemes to give a KES scheme with the sum of the time periods.

While we could do this with two independent KES schemes (i.e. two types) we only need it for two instances of the same scheme, and we save substantially on the size of the type and runtime dictionaries if we do it this way, especially when we start applying it recursively.

Instances

Instances details
Generic (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (SigKES (CompactSumKES h d)) ∷ TypeType Source #

Methods

fromSigKES (CompactSumKES h d) → Rep (SigKES (CompactSumKES h d)) x Source #

toRep (SigKES (CompactSumKES h d)) x → SigKES (CompactSumKES h d) Source #

Generic (UnsoundPureSignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (UnsoundPureSignKeyKES (CompactSumKES h d)) ∷ TypeType Source #

Generic (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (VerKeyKES (CompactSumKES h d)) ∷ TypeType Source #

KESAlgorithm d ⇒ Show (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

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

Defined in Cardano.Crypto.KES.CompactSum

HashAlgorithm h ⇒ Show (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

(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))) ⇒ FromCBOR (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

(SizeHash h ~ SeedSizeKES d, OptimizedKESAlgorithm d, UnsoundPureKESAlgorithm d, SodiumHashAlgorithm h, KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) ⇒ FromCBOR (UnsoundPureSignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

(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))) ⇒ FromCBOR (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

(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))) ⇒ ToCBOR (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

toCBORSigKES (CompactSumKES h d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (SigKES (CompactSumKES h d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SigKES (CompactSumKES h d)] → Size Source #

(SizeHash h ~ SeedSizeKES d, OptimizedKESAlgorithm d, UnsoundPureKESAlgorithm d, SodiumHashAlgorithm h, KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) ⇒ ToCBOR (UnsoundPureSignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

(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))) ⇒ ToCBOR (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

toCBORVerKeyKES (CompactSumKES h d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (VerKeyKES (CompactSumKES h d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [VerKeyKES (CompactSumKES h d)] → Size Source #

(DirectDeserialise (SignKeyKES d), DirectDeserialise (VerKeyKES d), KESAlgorithm d) ⇒ DirectDeserialise (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (SignKeyKES (CompactSumKES h d)) Source #

HashAlgorithm h ⇒ DirectDeserialise (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (VerKeyKES (CompactSumKES h d)) Source #

(DirectSerialise (SignKeyKES d), DirectSerialise (VerKeyKES d), KESAlgorithm d) ⇒ DirectSerialise (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → SignKeyKES (CompactSumKES h d) → m () Source #

DirectSerialise (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → VerKeyKES (CompactSumKES h d) → m () Source #

(NFData (SigKES d), NFData (VerKeyKES d)) ⇒ NFData (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnfSigKES (CompactSumKES h d) → () Source #

(NFData (SignKeyKES d), NFData (VerKeyKES d)) ⇒ NFData (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnfSignKeyKES (CompactSumKES h d) → () Source #

NFData (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnfVerKeyKES (CompactSumKES h d) → () Source #

KESAlgorithm d ⇒ Eq (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

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

Defined in Cardano.Crypto.KES.CompactSum

Eq (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KESAlgorithm d ⇒ NoThunks (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

NoThunks (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

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

Defined in Cardano.Crypto.KES.CompactSum

KESAlgorithm d ⇒ NoThunks (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

(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 #

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

Defined in Cardano.Crypto.KES.CompactSum

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

Defined in Cardano.Crypto.KES.CompactSum

(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 #

type Rep (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type Rep (SigKES (CompactSumKES h d)) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.CompactSum" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "SigCompactSumKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SigKES d)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d))))
type Rep (UnsoundPureSignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type Rep (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type Rep (VerKeyKES (CompactSumKES h d)) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.CompactSum" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "VerKeyCompactSumKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash h (VerKeyKES d, VerKeyKES d)))))
type ContextKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type SeedSizeKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

data SigKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

data SignKeyKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type Signable (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type SizeSigKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type SizeSignKeyKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type SizeVerKeyKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

data UnsoundPureSignKeyKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

newtype VerKeyKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

data family VerKeyKES v ∷ Type Source #

Instances

Instances details
Generic (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Associated Types

type Rep (VerKeyKES (CompactSingleKES d)) ∷ TypeType Source #

Generic (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (VerKeyKES (CompactSumKES h d)) ∷ TypeType Source #

Generic (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (VerKeyKES (MockKES t)) ∷ TypeType Source #

Methods

fromVerKeyKES (MockKES t) → Rep (VerKeyKES (MockKES t)) x Source #

toRep (VerKeyKES (MockKES t)) x → VerKeyKES (MockKES t) Source #

Generic (VerKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

type Rep (VerKeyKES NeverKES) ∷ TypeType Source #

Generic (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (VerKeyKES (SimpleKES d t)) ∷ TypeType Source #

Methods

fromVerKeyKES (SimpleKES d t) → Rep (VerKeyKES (SimpleKES d t)) x Source #

toRep (VerKeyKES (SimpleKES d t)) x → VerKeyKES (SimpleKES d t) Source #

Generic (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Associated Types

type Rep (VerKeyKES (SingleKES d)) ∷ TypeType Source #

Generic (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Associated Types

type Rep (VerKeyKES (SumKES h d)) ∷ TypeType Source #

Methods

fromVerKeyKES (SumKES h d) → Rep (VerKeyKES (SumKES h d)) x Source #

toRep (VerKeyKES (SumKES h d)) x → VerKeyKES (SumKES h d) Source #

DSIGNMAlgorithm d ⇒ Show (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

HashAlgorithm h ⇒ Show (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Show (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Show (VerKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNMAlgorithm d ⇒ Show (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d ⇒ Show (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

HashAlgorithm h ⇒ Show (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

showsPrecIntVerKeyKES (SumKES h d) → ShowS Source #

showVerKeyKES (SumKES h d) → String Source #

showList ∷ [VerKeyKES (SumKES h d)] → ShowS Source #

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

Defined in Cardano.Crypto.KES.CompactSingle

(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))) ⇒ FromCBOR (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t ⇒ FromCBOR (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

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

Defined in Cardano.Crypto.KES.Simple

DSIGNMAlgorithm d ⇒ FromCBOR (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) ⇒ FromCBOR (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

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

Defined in Cardano.Crypto.KES.CompactSingle

(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))) ⇒ ToCBOR (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

toCBORVerKeyKES (CompactSumKES h d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (VerKeyKES (CompactSumKES h d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [VerKeyKES (CompactSumKES h d)] → Size Source #

KnownNat t ⇒ ToCBOR (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

toCBORVerKeyKES (MockKES t) → Encoding Source #

encodedSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy (VerKeyKES (MockKES t)) → Size Source #

encodedListSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy [VerKeyKES (MockKES t)] → Size Source #

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

Defined in Cardano.Crypto.KES.Simple

Methods

toCBORVerKeyKES (SimpleKES d t) → Encoding Source #

encodedSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy (VerKeyKES (SimpleKES d t)) → Size Source #

encodedListSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy [VerKeyKES (SimpleKES d t)] → Size Source #

DSIGNMAlgorithm d ⇒ ToCBOR (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

toCBORVerKeyKES (SingleKES d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (VerKeyKES (SingleKES d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [VerKeyKES (SingleKES d)] → Size Source #

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) ⇒ ToCBOR (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

toCBORVerKeyKES (SumKES h d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (VerKeyKES (SumKES h d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [VerKeyKES (SumKES h d)] → Size Source #

DirectDeserialise (VerKeyDSIGN d) ⇒ DirectDeserialise (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (VerKeyKES (CompactSingleKES d)) Source #

HashAlgorithm h ⇒ DirectDeserialise (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (VerKeyKES (CompactSumKES h d)) Source #

KnownNat t ⇒ DirectDeserialise (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (VerKeyKES (MockKES t)) Source #

(DirectDeserialise (VerKeyDSIGN d), KnownNat t) ⇒ DirectDeserialise (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (VerKeyKES (SimpleKES d t)) Source #

DirectDeserialise (VerKeyDSIGN d) ⇒ DirectDeserialise (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (VerKeyKES (SingleKES d)) Source #

HashAlgorithm h ⇒ DirectDeserialise (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (VerKeyKES (SumKES h d)) Source #

DirectSerialise (VerKeyDSIGN d) ⇒ DirectSerialise (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → VerKeyKES (CompactSingleKES d) → m () Source #

DirectSerialise (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → VerKeyKES (CompactSumKES h d) → m () Source #

KnownNat t ⇒ DirectSerialise (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → VerKeyKES (MockKES t) → m () Source #

DirectSerialise (VerKeyDSIGN d) ⇒ DirectSerialise (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → VerKeyKES (SimpleKES d t) → m () Source #

DirectSerialise (VerKeyDSIGN d) ⇒ DirectSerialise (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → VerKeyKES (SingleKES d) → m () Source #

DirectSerialise (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → VerKeyKES (SumKES h d) → m () Source #

NFData (VerKeyDSIGN d) ⇒ NFData (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

rnfVerKeyKES (CompactSingleKES d) → () Source #

NFData (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnfVerKeyKES (CompactSumKES h d) → () Source #

NFData (VerKeyDSIGN d) ⇒ NFData (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

rnfVerKeyKES (SingleKES d) → () Source #

NFData (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

rnfVerKeyKES (SumKES h d) → () Source #

DSIGNMAlgorithm d ⇒ Eq (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Eq (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Eq (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Eq (VerKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNMAlgorithm d ⇒ Eq (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

(==)VerKeyKES (SimpleKES d t) → VerKeyKES (SimpleKES d t) → Bool Source #

(/=)VerKeyKES (SimpleKES d t) → VerKeyKES (SimpleKES d t) → Bool Source #

DSIGNAlgorithm d ⇒ Eq (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Eq (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

(==)VerKeyKES (SumKES h d) → VerKeyKES (SumKES h d) → Bool Source #

(/=)VerKeyKES (SumKES h d) → VerKeyKES (SumKES h d) → Bool Source #

(TypeError ('Text "Ord not supported for verification keys, use the hash instead") ∷ Constraint, KESAlgorithm v) ⇒ Ord (VerKeyKES v) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

DSIGNMAlgorithm d ⇒ NoThunks (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d ⇒ NoThunks (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

NoThunks (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

NoThunks (VerKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNMAlgorithm d ⇒ NoThunks (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNMAlgorithm d ⇒ NoThunks (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d ⇒ NoThunks (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

data VerKeyKES NeverKES Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

type Rep (VerKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

type Rep (VerKeyKES (CompactSingleKES d)) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.CompactSingle" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "VerKeyCompactSingleKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN d))))
type Rep (VerKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type Rep (VerKeyKES (CompactSumKES h d)) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.CompactSum" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "VerKeyCompactSumKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash h (VerKeyKES d, VerKeyKES d)))))
type Rep (VerKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

type Rep (VerKeyKES (MockKES t)) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.Mock" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "VerKeyMockKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
type Rep (VerKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

type Rep (VerKeyKES NeverKES) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.NeverUsed" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "NeverUsedVerKeyKES" 'PrefixI 'False) (U1TypeType))
type Rep (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

type Rep (VerKeyKES (SimpleKES d t)) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.Simple" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "ThunkyVerKeySimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector (VerKeyDSIGN d)))))
type Rep (VerKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

type Rep (VerKeyKES (SingleKES d)) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.Single" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "VerKeySingleKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN d))))
type Rep (VerKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

type Rep (VerKeyKES (SumKES h d)) = D1 ('MetaData "VerKeyKES" "Cardano.Crypto.KES.Sum" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "VerKeySumKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash h (VerKeyKES d, VerKeyKES d)))))
newtype VerKeyKES (CompactSingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

newtype VerKeyKES (MockKES t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

newtype VerKeyKES (SingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

newtype VerKeyKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

newtype VerKeyKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

newtype VerKeyKES (SumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

data family SignKeyKES v ∷ Type Source #

Instances

Instances details
Generic (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (SignKeyKES (MockKES t)) ∷ TypeType Source #

Generic (SignKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

type Rep (SignKeyKES NeverKES) ∷ TypeType Source #

Generic (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SignKeyKES (SimpleKES d t)) ∷ TypeType Source #

Methods

fromSignKeyKES (SimpleKES d t) → Rep (SignKeyKES (SimpleKES d t)) x Source #

toRep (SignKeyKES (SimpleKES d t)) x → SignKeyKES (SimpleKES d t) Source #

Show (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Show (SignKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

(DSIGNMAlgorithm d, Show (SignKeyDSIGNM d)) ⇒ Show (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DirectDeserialise (SignKeyDSIGNM d) ⇒ DirectDeserialise (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (SignKeyKES (CompactSingleKES d)) Source #

(DirectDeserialise (SignKeyKES d), DirectDeserialise (VerKeyKES d), KESAlgorithm d) ⇒ DirectDeserialise (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (SignKeyKES (CompactSumKES h d)) Source #

KnownNat t ⇒ DirectDeserialise (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (SignKeyKES (MockKES t)) Source #

(DirectDeserialise (SignKeyDSIGNM d), KnownNat t) ⇒ DirectDeserialise (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (SignKeyKES (SimpleKES d t)) Source #

DirectDeserialise (SignKeyDSIGNM d) ⇒ DirectDeserialise (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (SignKeyKES (SingleKES d)) Source #

(DirectDeserialise (SignKeyKES d), DirectDeserialise (VerKeyKES d), KESAlgorithm d) ⇒ DirectDeserialise (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

directDeserialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → m (SignKeyKES (SumKES h d)) Source #

DirectSerialise (SignKeyDSIGNM d) ⇒ DirectSerialise (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → SignKeyKES (CompactSingleKES d) → m () Source #

(DirectSerialise (SignKeyKES d), DirectSerialise (VerKeyKES d), KESAlgorithm d) ⇒ DirectSerialise (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → SignKeyKES (CompactSumKES h d) → m () Source #

KnownNat t ⇒ DirectSerialise (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → SignKeyKES (MockKES t) → m () Source #

DirectSerialise (SignKeyDSIGNM d) ⇒ DirectSerialise (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → SignKeyKES (SimpleKES d t) → m () Source #

DirectSerialise (SignKeyDSIGNM d) ⇒ DirectSerialise (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → SignKeyKES (SingleKES d) → m () Source #

(DirectSerialise (SignKeyKES d), DirectSerialise (VerKeyKES d), KESAlgorithm d) ⇒ DirectSerialise (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

directSerialise ∷ (MonadST m, MonadThrow m) ⇒ (Ptr CCharCSize → m ()) → SignKeyKES (SumKES h d) → m () Source #

NFData (SignKeyDSIGNM d) ⇒ NFData (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

rnfSignKeyKES (CompactSingleKES d) → () Source #

(NFData (SignKeyKES d), NFData (VerKeyKES d)) ⇒ NFData (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnfSignKeyKES (CompactSumKES h d) → () Source #

NFData (SignKeyDSIGNM d) ⇒ NFData (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

rnfSignKeyKES (SingleKES d) → () Source #

(NFData (SignKeyKES d), NFData (VerKeyKES d)) ⇒ NFData (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

rnfSignKeyKES (SumKES h d) → () Source #

Eq (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Eq (SignKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

(TypeError ('Text "Ord not supported for signing keys, use the hash instead") ∷ Constraint, Eq (SignKeyKES v)) ⇒ Ord (SignKeyKES v) Source # 
Instance details

Defined in Cardano.Crypto.KES.Class

DSIGNMAlgorithm d ⇒ NoThunks (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

NoThunks (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

NoThunks (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

NoThunks (SignKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNMAlgorithm d ⇒ NoThunks (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNMAlgorithm d ⇒ NoThunks (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

NoThunks (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

data SignKeyKES NeverKES Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

type Rep (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

type Rep (SignKeyKES (MockKES t)) = D1 ('MetaData "SignKeyKES" "Cardano.Crypto.KES.Mock" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "SignKeyMockKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES (MockKES t))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Period)))
type Rep (SignKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

type Rep (SignKeyKES NeverKES) = D1 ('MetaData "SignKeyKES" "Cardano.Crypto.KES.NeverUsed" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "NeverUsedSignKeyKES" 'PrefixI 'False) (U1TypeType))
type Rep (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

type Rep (SignKeyKES (SimpleKES d t)) = D1 ('MetaData "SignKeyKES" "Cardano.Crypto.KES.Simple" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "ThunkySignKeySimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector (SignKeyDSIGNM d)))))
newtype SignKeyKES (CompactSingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

data SignKeyKES (MockKES t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

newtype SignKeyKES (SingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

data SignKeyKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

newtype SignKeyKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

data SignKeyKES (SumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

data family SigKES v ∷ Type Source #

Instances

Instances details
Generic (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Associated Types

type Rep (SigKES (CompactSingleKES d)) ∷ TypeType Source #

Generic (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (SigKES (CompactSumKES h d)) ∷ TypeType Source #

Methods

fromSigKES (CompactSumKES h d) → Rep (SigKES (CompactSumKES h d)) x Source #

toRep (SigKES (CompactSumKES h d)) x → SigKES (CompactSumKES h d) Source #

Generic (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (SigKES (MockKES t)) ∷ TypeType Source #

Methods

fromSigKES (MockKES t) → Rep (SigKES (MockKES t)) x Source #

toRep (SigKES (MockKES t)) x → SigKES (MockKES t) Source #

Generic (SigKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

type Rep (SigKES NeverKES) ∷ TypeType Source #

Generic (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SigKES (SimpleKES d t)) ∷ TypeType Source #

Methods

fromSigKES (SimpleKES d t) → Rep (SigKES (SimpleKES d t)) x Source #

toRep (SigKES (SimpleKES d t)) x → SigKES (SimpleKES d t) Source #

Generic (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Associated Types

type Rep (SigKES (SingleKES d)) ∷ TypeType Source #

Methods

fromSigKES (SingleKES d) → Rep (SigKES (SingleKES d)) x Source #

toRep (SigKES (SingleKES d)) x → SigKES (SingleKES d) Source #

Generic (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Associated Types

type Rep (SigKES (SumKES h d)) ∷ TypeType Source #

Methods

fromSigKES (SumKES h d) → Rep (SigKES (SumKES h d)) x Source #

toRep (SigKES (SumKES h d)) x → SigKES (SumKES h d) Source #

DSIGNMAlgorithm d ⇒ Show (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d ⇒ Show (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Show (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Show (SigKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNMAlgorithm d ⇒ Show (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

showsPrecIntSigKES (SimpleKES d t) → ShowS Source #

showSigKES (SimpleKES d t) → String Source #

showList ∷ [SigKES (SimpleKES d t)] → ShowS Source #

DSIGNAlgorithm d ⇒ Show (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

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

Defined in Cardano.Crypto.KES.Sum

Methods

showsPrecIntSigKES (SumKES h d) → ShowS Source #

showSigKES (SumKES h d) → String Source #

showList ∷ [SigKES (SumKES h d)] → ShowS Source #

(DSIGNMAlgorithm d, KnownNat (SizeSigKES (CompactSingleKES d))) ⇒ FromCBOR (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(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))) ⇒ FromCBOR (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t ⇒ FromCBOR (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

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

Defined in Cardano.Crypto.KES.Simple

DSIGNMAlgorithm d ⇒ FromCBOR (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) ⇒ FromCBOR (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

fromCBORDecoder s (SigKES (SumKES h d)) Source #

labelProxy (SigKES (SumKES h d)) → Text Source #

(DSIGNMAlgorithm d, KnownNat (SizeSigKES (CompactSingleKES d))) ⇒ ToCBOR (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(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))) ⇒ ToCBOR (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

toCBORSigKES (CompactSumKES h d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (SigKES (CompactSumKES h d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SigKES (CompactSumKES h d)] → Size Source #

KnownNat t ⇒ ToCBOR (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

toCBORSigKES (MockKES t) → Encoding Source #

encodedSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy (SigKES (MockKES t)) → Size Source #

encodedListSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy [SigKES (MockKES t)] → Size Source #

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

Defined in Cardano.Crypto.KES.Simple

Methods

toCBORSigKES (SimpleKES d t) → Encoding Source #

encodedSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy (SigKES (SimpleKES d t)) → Size Source #

encodedListSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy [SigKES (SimpleKES d t)] → Size Source #

DSIGNMAlgorithm d ⇒ ToCBOR (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

toCBORSigKES (SingleKES d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (SigKES (SingleKES d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SigKES (SingleKES d)] → Size Source #

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) ⇒ ToCBOR (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

toCBORSigKES (SumKES h d) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (SigKES (SumKES h d)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SigKES (SumKES h d)] → Size Source #

(NFData (SigDSIGN d), NFData (VerKeyDSIGN d)) ⇒ NFData (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

rnfSigKES (CompactSingleKES d) → () Source #

(NFData (SigKES d), NFData (VerKeyKES d)) ⇒ NFData (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnfSigKES (CompactSumKES h d) → () Source #

NFData (SigDSIGN d) ⇒ NFData (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

rnfSigKES (SingleKES d) → () Source #

(NFData (SigKES d), NFData (VerKeyKES d)) ⇒ NFData (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

rnfSigKES (SumKES h d) → () Source #

DSIGNMAlgorithm d ⇒ Eq (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d ⇒ Eq (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Eq (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

(==)SigKES (MockKES t) → SigKES (MockKES t) → Bool Source #

(/=)SigKES (MockKES t) → SigKES (MockKES t) → Bool Source #

Eq (SigKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNMAlgorithm d ⇒ Eq (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

(==)SigKES (SimpleKES d t) → SigKES (SimpleKES d t) → Bool Source #

(/=)SigKES (SimpleKES d t) → SigKES (SimpleKES d t) → Bool Source #

DSIGNAlgorithm d ⇒ Eq (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

(==)SigKES (SingleKES d) → SigKES (SingleKES d) → Bool Source #

(/=)SigKES (SingleKES d) → SigKES (SingleKES d) → Bool Source #

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

Defined in Cardano.Crypto.KES.Sum

Methods

(==)SigKES (SumKES h d) → SigKES (SumKES h d) → Bool Source #

(/=)SigKES (SumKES h d) → SigKES (SumKES h d) → Bool Source #

DSIGNMAlgorithm d ⇒ NoThunks (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d ⇒ NoThunks (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

NoThunks (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

NoThunks (SigKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNMAlgorithm d ⇒ NoThunks (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d ⇒ NoThunks (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d ⇒ NoThunks (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

data SigKES NeverKES Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

type Rep (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

type Rep (SigKES (CompactSingleKES d)) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.CompactSingle" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "SigCompactSingleKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SigDSIGN d)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyDSIGN d))))
type Rep (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type Rep (SigKES (CompactSumKES h d)) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.CompactSum" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "SigCompactSumKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SigKES d)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d))))
type Rep (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

type Rep (SigKES (MockKES t)) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.Mock" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "SigMockKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash ShortHash ())) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyKES (MockKES t)))))
type Rep (SigKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

type Rep (SigKES NeverKES) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.NeverUsed" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "NeverUsedSigKES" 'PrefixI 'False) (U1TypeType))
type Rep (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

type Rep (SigKES (SimpleKES d t)) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.Simple" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "SigSimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SigDSIGN d))))
type Rep (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

type Rep (SigKES (SingleKES d)) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.Single" "cardano-crypto-class-2.2.0.0-inplace" 'True) (C1 ('MetaCons "SigSingleKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SigDSIGN d))))
type Rep (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

type Rep (SigKES (SumKES h d)) = D1 ('MetaData "SigKES" "Cardano.Crypto.KES.Sum" "cardano-crypto-class-2.2.0.0-inplace" 'False) (C1 ('MetaCons "SigSumKES" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SigKES d)) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d)))))
data SigKES (CompactSingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

data SigKES (MockKES t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

newtype SigKES (SingleKES d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

data SigKES (CompactSumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

newtype SigKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

data SigKES (SumKES h d) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

data SigKES (SumKES h d) = SigSumKES !(SigKES d) !(VerKeyKES d) !(VerKeyKES d)

Type aliases for powers of binary sums

type CompactSum0KES d = CompactSingleKES d Source #

A 2^0 period KES

type CompactSum1KES d h = CompactSumKES h (CompactSum0KES d) Source #

A 2^1 period KES

type CompactSum2KES d h = CompactSumKES h (CompactSum1KES d h) Source #

A 2^2 period KES

type CompactSum3KES d h = CompactSumKES h (CompactSum2KES d h) Source #

A 2^3 period KES

type CompactSum4KES d h = CompactSumKES h (CompactSum3KES d h) Source #

A 2^4 period KES

type CompactSum5KES d h = CompactSumKES h (CompactSum4KES d h) Source #

A 2^5 period KES

type CompactSum6KES d h = CompactSumKES h (CompactSum5KES d h) Source #

A 2^6 period KES

type CompactSum7KES d h = CompactSumKES h (CompactSum6KES d h) Source #

A 2^7 period KES