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

Cardano.Crypto.DSIGNM.Class

Description

Abstract digital signatures.

Synopsis

DSIGNMM algorithm class

class (Typeable v, Show (VerKeyDSIGNM v), Eq (VerKeyDSIGNM v), Show (SignKeyDSIGNM v), Show (SigDSIGNM v), Eq (SigDSIGNM v), NoThunks (SigDSIGNM v), NoThunks (SignKeyDSIGNM v), NoThunks (VerKeyDSIGNM v), KnownNat (SeedSizeDSIGNM v), KnownNat (SizeVerKeyDSIGNM v), KnownNat (SizeSignKeyDSIGNM v), KnownNat (SizeSigDSIGNM v)) => DSIGNMAlgorithmBase v where #

Associated Types

type SeedSizeDSIGNM v :: Nat #

type SizeVerKeyDSIGNM v :: Nat #

type SizeSignKeyDSIGNM v :: Nat #

type SizeSigDSIGNM v :: Nat #

data VerKeyDSIGNM v :: Type #

data SignKeyDSIGNM v :: Type #

data SigDSIGNM v :: Type #

type ContextDSIGNM v :: Type #

Context required to run the DSIGNM algorithm

Unit by default (no context required)

type ContextDSIGNM v = ()

type SignableM v :: Type -> Constraint #

type SignableM v = Empty

data MLockedSeed n #

A seed of size n, stored in mlocked memory. This is required to prevent the seed from leaking to disk via swapping and reclaiming or scanning memory after its content has been moved.

Instances

Instances details
(MonadSodium m, MonadST m, KnownNat n) => MEq m (MLockedSeed n) # 
Instance details

Defined in Cardano.Crypto.MLockedSeed

Methods

equalsM :: MLockedSeed n -> MLockedSeed n -> m Bool #

NFData (MLockedSeed n) # 
Instance details

Defined in Cardano.Crypto.MLockedSeed

Methods

rnf :: MLockedSeed n -> () Source #

NoThunks (MLockedSeed n) # 
Instance details

Defined in Cardano.Crypto.MLockedSeed

seedSizeDSIGNM :: forall v proxy. DSIGNMAlgorithmBase v => proxy v -> Word #

The upper bound on the seed size needed by genKeyDSIGNM

sizeVerKeyDSIGNM :: forall v proxy. DSIGNMAlgorithmBase v => proxy v -> Word #

sizeSignKeyDSIGNM :: forall v proxy. DSIGNMAlgorithmBase v => proxy v -> Word #

sizeSigDSIGNM :: forall v proxy. DSIGNMAlgorithmBase v => proxy v -> Word #

SignedDSIGNM wrapper

newtype SignedDSIGNM v a #

Constructors

SignedDSIGNM (SigDSIGNM v) 

Instances

Instances details
Generic (SignedDSIGNM v a) # 
Instance details

Defined in Cardano.Crypto.DSIGNM.Class

Associated Types

type Rep (SignedDSIGNM v a) :: Type -> Type Source #

Methods

from :: SignedDSIGNM v a -> Rep (SignedDSIGNM v a) x Source #

to :: Rep (SignedDSIGNM v a) x -> SignedDSIGNM v a Source #

DSIGNMAlgorithmBase v => Show (SignedDSIGNM v a) # 
Instance details

Defined in Cardano.Crypto.DSIGNM.Class

DSIGNMAlgorithmBase v => Eq (SignedDSIGNM v a) # 
Instance details

Defined in Cardano.Crypto.DSIGNM.Class

DSIGNMAlgorithmBase v => NoThunks (SignedDSIGNM v a) # 
Instance details

Defined in Cardano.Crypto.DSIGNM.Class

type Rep (SignedDSIGNM v a) # 
Instance details

Defined in Cardano.Crypto.DSIGNM.Class

type Rep (SignedDSIGNM v a) = D1 ('MetaData "SignedDSIGNM" "Cardano.Crypto.DSIGNM.Class" "cardano-crypto-class-2.1.1.0-inplace" 'True) (C1 ('MetaCons "SignedDSIGNM" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SigDSIGNM v))))

CBOR encoding and decoding

Encoded Size expresssions

encodedVerKeyDSIGNMSizeExpr :: forall v. DSIGNMAlgorithmBase v => Proxy (VerKeyDSIGNM v) -> Size #

Size expression for VerKeyDSIGNM which is using sizeVerKeyDSIGNM encoded as Size.

encodedSignKeyDSIGNMSizeExpr :: forall v. DSIGNMAlgorithmBase v => Proxy (SignKeyDSIGNM v) -> Size #

Size expression for SignKeyDSIGNM which is using sizeSignKeyDSIGNM encoded as Size.

encodedSigDSIGNMSizeExpr :: forall v. DSIGNMAlgorithmBase v => Proxy (SigDSIGNM v) -> Size #

Size expression for SigDSIGNM which is using sizeSigDSIGNM encoded as Size.

Unsound API

class DSIGNMAlgorithm m v => UnsoundDSIGNMAlgorithm m v where #

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