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

Cardano.Crypto.KES.Simple

Description

Mock key evolving signatures.

Documentation

data SimpleKES d (t :: Nat) Source #

Instances

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

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SigKES (SimpleKES d t)) :: Type -> Type Source #

Methods

from :: SigKES (SimpleKES d t) -> Rep (SigKES (SimpleKES d t)) x Source #

to :: Rep (SigKES (SimpleKES d t)) x -> SigKES (SimpleKES d t) Source #

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

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SignKeyKES (SimpleKES d t)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (VerKeyKES (SimpleKES d t)) :: Type -> Type Source #

DSIGNAlgorithm d => Show (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => Show (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => Show (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => FromCBOR (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => FromCBOR (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => FromCBOR (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => ToCBOR (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

toCBOR :: SigKES (SimpleKES d t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SigKES (SimpleKES d t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SigKES (SimpleKES d t)] -> Size Source #

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => ToCBOR (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

toCBOR :: SignKeyKES (SimpleKES d t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SignKeyKES (SimpleKES d t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SignKeyKES (SimpleKES d t)] -> Size Source #

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => ToCBOR (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

toCBOR :: VerKeyKES (SimpleKES d t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (VerKeyKES (SimpleKES d t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [VerKeyKES (SimpleKES d t)] -> Size Source #

DSIGNAlgorithm 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 (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => NoThunks (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => NoThunks (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => NoThunks (VerKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => KESAlgorithm (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Associated Types

type SeedSizeKES (SimpleKES d t) :: Nat Source #

data VerKeyKES (SimpleKES d t) Source #

data SignKeyKES (SimpleKES d t) Source #

data SigKES (SimpleKES d t) Source #

type ContextKES (SimpleKES d t) Source #

type Signable (SimpleKES d t) :: Type -> Constraint Source #

Methods

algorithmNameKES :: proxy (SimpleKES d t) -> String Source #

deriveVerKeyKES :: SignKeyKES (SimpleKES d t) -> VerKeyKES (SimpleKES d t) Source #

hashVerKeyKES :: HashAlgorithm h => VerKeyKES (SimpleKES d t) -> Hash h (VerKeyKES (SimpleKES d t)) Source #

signKES :: (Signable (SimpleKES d t) a, HasCallStack) => ContextKES (SimpleKES d t) -> Period -> a -> SignKeyKES (SimpleKES d t) -> SigKES (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 #

updateKES :: ContextKES (SimpleKES d t) -> SignKeyKES (SimpleKES d t) -> Period -> Maybe (SignKeyKES (SimpleKES d t)) Source #

totalPeriodsKES :: proxy (SimpleKES d t) -> Word Source #

genKeyKES :: Seed -> SignKeyKES (SimpleKES d t) Source #

seedSizeKES :: proxy (SimpleKES d t) -> Word Source #

forgetSignKeyKES :: SignKeyKES (SimpleKES d t) -> IO () Source #

sizeVerKeyKES :: proxy (SimpleKES d t) -> Word Source #

sizeSignKeyKES :: proxy (SimpleKES d t) -> Word Source #

sizeSigKES :: proxy (SimpleKES d t) -> Word Source #

rawSerialiseVerKeyKES :: VerKeyKES (SimpleKES d t) -> ByteString Source #

rawSerialiseSignKeyKES :: SignKeyKES (SimpleKES d t) -> ByteString Source #

rawSerialiseSigKES :: SigKES (SimpleKES d t) -> ByteString Source #

rawDeserialiseVerKeyKES :: ByteString -> Maybe (VerKeyKES (SimpleKES d t)) Source #

rawDeserialiseSignKeyKES :: ByteString -> Maybe (SignKeyKES (SimpleKES d t)) Source #

rawDeserialiseSigKES :: ByteString -> Maybe (SigKES (SimpleKES d t)) Source #

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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "SigSimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SigDSIGN d))))
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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "ThunkySignKeySimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector (SignKeyDSIGN d)))))
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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "ThunkyVerKeySimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector (VerKeyDSIGN d)))))
type ContextKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

type SeedSizeKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

newtype SigKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

newtype SignKeyKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

type Signable (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

type Signable (SimpleKES d t) = Signable d
newtype VerKeyKES (SimpleKES d t) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

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)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (SigKES (CompactSumKES h d)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (SigKES (MockKES t)) :: Type -> Type Source #

Methods

from :: SigKES (MockKES t) -> Rep (SigKES (MockKES t)) x Source #

to :: Rep (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) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SigKES (SimpleKES d t)) :: Type -> Type Source #

Methods

from :: SigKES (SimpleKES d t) -> Rep (SigKES (SimpleKES d t)) x Source #

to :: Rep (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)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Sum

Associated Types

type Rep (SigKES (SumKES h d)) :: Type -> Type Source #

Methods

from :: SigKES (SumKES h d) -> Rep (SigKES (SumKES h d)) x Source #

to :: Rep (SigKES (SumKES h d)) x -> SigKES (SumKES h d) Source #

DSIGNAlgorithm 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

DSIGNAlgorithm d => Show (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => Show (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d => Show (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

DSIGNAlgorithm d => FromCBOR (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(OptimizedKESAlgorithm d, HashAlgorithm h) => 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

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => FromCBOR (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => FromCBOR (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm d, HashAlgorithm h) => FromCBOR (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

fromCBOR :: Decoder s (SigKES (SumKES h d)) Source #

label :: Proxy (SigKES (SumKES h d)) -> Text Source #

DSIGNAlgorithm d => ToCBOR (SigKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(OptimizedKESAlgorithm d, HashAlgorithm h) => ToCBOR (SigKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

toCBOR :: SigKES (CompactSumKES h d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigKES (CompactSumKES h d)) -> Size Source #

encodedListSizeExpr :: (forall 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

toCBOR :: SigKES (MockKES t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SigKES (MockKES t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SigKES (MockKES t)] -> Size Source #

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => ToCBOR (SigKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

toCBOR :: SigKES (SimpleKES d t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SigKES (SimpleKES d t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SigKES (SimpleKES d t)] -> Size Source #

DSIGNAlgorithm d => ToCBOR (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

toCBOR :: SigKES (SingleKES d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigKES (SingleKES d)) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigKES (SingleKES d)] -> Size Source #

(KESAlgorithm d, HashAlgorithm h) => ToCBOR (SigKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

toCBOR :: SigKES (SumKES h d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigKES (SumKES h d)) -> Size Source #

encodedListSizeExpr :: (forall 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

rnf :: SigKES (CompactSingleKES d) -> () Source #

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

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnf :: SigKES (CompactSumKES h d) -> () Source #

NFData (SigDSIGN d) => NFData (SigKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

rnf :: SigKES (SingleKES d) -> () Source #

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

Defined in Cardano.Crypto.KES.Sum

Methods

rnf :: SigKES (SumKES h d) -> () Source #

DSIGNAlgorithm 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

DSIGNAlgorithm 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

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

(TypeError ('Text "Ord not supported for signing keys, use the hash instead") :: Constraint) => Ord (SigKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

DSIGNAlgorithm 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

DSIGNAlgorithm 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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "SigCompactSingleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SigDSIGN d)) :*: S1 ('MetaSel ('Nothing :: Maybe 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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "SigCompactSumKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SigKES d)) :*: S1 ('MetaSel ('Nothing :: Maybe 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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "SigMockKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash ShortHash ())) :*: S1 ('MetaSel ('Nothing :: Maybe 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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "NeverUsedSigKES" 'PrefixI 'False) (U1 :: Type -> Type))
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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "SigSimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "SigSingleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "SigSumKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SigKES d)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d)) :*: S1 ('MetaSel ('Nothing :: Maybe 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)

data family SignKeyKES v :: Type Source #

Instances

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

Defined in Cardano.Crypto.KES.CompactSingle

Associated Types

type Rep (SignKeyKES (CompactSingleKES d)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.CompactSum

Associated Types

type Rep (SignKeyKES (CompactSumKES h d)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Mock

Associated Types

type Rep (SignKeyKES (MockKES t)) :: Type -> Type Source #

Generic (SignKeyKES NeverKES) Source # 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

Associated Types

type Rep (SignKeyKES NeverKES) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Simple

Associated Types

type Rep (SignKeyKES (SimpleKES d t)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Single

Associated Types

type Rep (SignKeyKES (SingleKES d)) :: Type -> Type Source #

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

Defined in Cardano.Crypto.KES.Sum

Associated Types

type Rep (SignKeyKES (SumKES h d)) :: Type -> Type Source #

Methods

from :: SignKeyKES (SumKES h d) -> Rep (SignKeyKES (SumKES h d)) x Source #

to :: Rep (SignKeyKES (SumKES h d)) x -> SignKeyKES (SumKES h d) Source #

DSIGNAlgorithm d => Show (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d => Show (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

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

DSIGNAlgorithm d => Show (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => Show (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d => Show (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

DSIGNAlgorithm d => FromCBOR (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(OptimizedKESAlgorithm d, HashAlgorithm h) => FromCBOR (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t => FromCBOR (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => FromCBOR (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => FromCBOR (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm d, HashAlgorithm h) => FromCBOR (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

DSIGNAlgorithm d => ToCBOR (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(OptimizedKESAlgorithm d, HashAlgorithm h) => ToCBOR (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t => ToCBOR (SignKeyKES (MockKES t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

toCBOR :: SignKeyKES (MockKES t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SignKeyKES (MockKES t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SignKeyKES (MockKES t)] -> Size Source #

(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) => ToCBOR (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

toCBOR :: SignKeyKES (SimpleKES d t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SignKeyKES (SimpleKES d t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SignKeyKES (SimpleKES d t)] -> Size Source #

DSIGNAlgorithm d => ToCBOR (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm d, HashAlgorithm h) => ToCBOR (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

toCBOR :: SignKeyKES (SumKES h d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyKES (SumKES h d)) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyKES (SumKES h d)] -> Size Source #

NFData (SignKeyDSIGN d) => NFData (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

Methods

rnf :: SignKeyKES (CompactSingleKES d) -> () Source #

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

Defined in Cardano.Crypto.KES.CompactSum

Methods

rnf :: SignKeyKES (CompactSumKES h d) -> () Source #

NFData (SignKeyDSIGN d) => NFData (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

rnf :: SignKeyKES (SingleKES d) -> () Source #

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

Defined in Cardano.Crypto.KES.Sum

Methods

rnf :: SignKeyKES (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

DSIGNAlgorithm d => NoThunks (SignKeyKES (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d => 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

DSIGNAlgorithm d => NoThunks (SignKeyKES (SimpleKES d t)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d => NoThunks (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d => 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 (CompactSingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

type Rep (SignKeyKES (CompactSingleKES d)) = D1 ('MetaData "SignKeyKES" "Cardano.Crypto.KES.CompactSingle" "cardano-crypto-class-2.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "SignKeyCompactSingleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SignKeyDSIGN d))))
type Rep (SignKeyKES (CompactSumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

type Rep (SignKeyKES (CompactSumKES h d)) = D1 ('MetaData "SignKeyKES" "Cardano.Crypto.KES.CompactSum" "cardano-crypto-class-2.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "SignKeyCompactSumKES" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyKES d)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Seed)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d)))))
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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "SignKeyMockKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES (MockKES t))) :*: S1 ('MetaSel ('Nothing :: Maybe 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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "NeverUsedSignKeyKES" 'PrefixI 'False) (U1 :: Type -> Type))
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.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "ThunkySignKeySimpleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector (SignKeyDSIGN d)))))
type Rep (SignKeyKES (SingleKES d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Single

type Rep (SignKeyKES (SingleKES d)) = D1 ('MetaData "SignKeyKES" "Cardano.Crypto.KES.Single" "cardano-crypto-class-2.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'True) (C1 ('MetaCons "SignKeySingleKES" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SignKeyDSIGN d))))
type Rep (SignKeyKES (SumKES h d)) Source # 
Instance details

Defined in Cardano.Crypto.KES.Sum

type Rep (SignKeyKES (SumKES h d)) = D1 ('MetaData "SignKeyKES" "Cardano.Crypto.KES.Sum" "cardano-crypto-class-2.0.0.0.0.0.0.2-DK6Ti6yI0b4E6vuoX0zDQ9" 'False) (C1 ('MetaCons "SignKeySumKES" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyKES d)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Seed)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES d)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VerKeyKES 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