cardano-crypto-wrapper-1.3.0: Cryptographic primitives used in the Cardano project
Safe HaskellNone
LanguageHaskell2010

Cardano.Crypto.Signing

Synopsis

Documentation

data SignTag Source #

To protect against replay attacks (i.e. when an attacker intercepts a signed piece of data and later sends it again), we add a tag to all data that we sign. This ensures that even if some bytestring can be deserialized into two different types of messages (A and B), the attacker can't take message A and send it as message B.

We also automatically add the network tag (protocolMagic) whenever it makes sense, to ensure that things intended for testnet won't work for mainnet.

Constructors

SignForTestingOnly

Anything (to be used for testing only)

SignTx

Tx: TxSigData

SignRedeemTx

Redeem tx: TxSigData

SignVssCert

Vss certificate: (VssVerificationKey, EpochNumber)

SignUSProposal

Update proposal: UpdateProposalToSign

SignCommitment

Commitment: (EpochNumber, Commitment)

SignUSVote

US proposal vote: (UpId, Bool)

SignBlock VerificationKey

Block header: ToSign

This constructor takes the VerificationKey of the delegation certificate issuer, which is prepended to the signature as part of the sign tag

SignCertificate

Certificate: Certificate

Instances

Instances details
Eq SignTag Source # 
Instance details

Defined in Cardano.Crypto.Signing.Tag

Methods

(==) :: SignTag -> SignTag -> Bool #

(/=) :: SignTag -> SignTag -> Bool #

Ord SignTag Source # 
Instance details

Defined in Cardano.Crypto.Signing.Tag

Show SignTag Source # 
Instance details

Defined in Cardano.Crypto.Signing.Tag

Generic SignTag Source # 
Instance details

Defined in Cardano.Crypto.Signing.Tag

Associated Types

type Rep SignTag :: Type -> Type #

Methods

from :: SignTag -> Rep SignTag x #

to :: Rep SignTag x -> SignTag #

Buildable SignTag Source # 
Instance details

Defined in Cardano.Crypto.Signing.Tag

type Rep SignTag Source # 
Instance details

Defined in Cardano.Crypto.Signing.Tag

type Rep SignTag = D1 ('MetaData "SignTag" "Cardano.Crypto.Signing.Tag" "cardano-crypto-wrapper-1.3.0-6xpOK9u3M8m70P8UdE8hNf" 'False) (((C1 ('MetaCons "SignForTestingOnly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SignTx" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SignRedeemTx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SignVssCert" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SignUSProposal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SignCommitment" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SignUSVote" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SignBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VerificationKey)) :+: C1 ('MetaCons "SignCertificate" 'PrefixI 'False) (U1 :: Type -> Type)))))

signTag :: ProtocolMagicId -> SignTag -> ByteString Source #

Get magic bytes corresponding to a SignTag. Guaranteed to be different (and begin with a different byte) for different tags.

signTagDecoded :: Annotated ProtocolMagicId ByteString -> SignTag -> ByteString Source #

Get magic bytes corresponding to a SignTag, taking ProtocolMagic bytes from the annotation

Signature

newtype Signature a Source #

Wrapper around XSignature

Constructors

Signature XSignature 

Instances

Instances details
Monad m => ToJSON m (Signature w) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

toJSON :: Signature w -> m JSValue Source #

(Typeable x, MonadError SchemaError m) => FromJSON m (Signature x) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

fromJSON :: JSValue -> m (Signature x) Source #

Eq (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

(==) :: Signature a -> Signature a -> Bool #

(/=) :: Signature a -> Signature a -> Bool #

Ord (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Show (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Generic (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Associated Types

type Rep (Signature a) :: Type -> Type #

Methods

from :: Signature a -> Rep (Signature a) x #

to :: Rep (Signature a) x -> Signature a #

ToJSON (Signature w) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

FromJSON (Signature w) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Typeable a => ToCBOR (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

toCBOR :: Signature a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Signature a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Signature a] -> Size Source #

Typeable a => FromCBOR (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

NFData (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

rnf :: Signature a -> () #

Buildable (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

build :: Signature a -> Builder Source #

NoThunks (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

type Rep (Signature a) Source # 
Instance details

Defined in Cardano.Crypto.Signing.Signature

type Rep (Signature a) = D1 ('MetaData "Signature" "Cardano.Crypto.Signing.Signature" "cardano-crypto-wrapper-1.3.0-6xpOK9u3M8m70P8UdE8hNf" 'True) (C1 ('MetaCons "Signature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XSignature)))

fullSignatureHexF :: Format r (Signature a -> r) Source #

Formatter for Signature to show it in hex.

parseFullSignature :: Text -> Either SignatureParseError (Signature a) Source #

Parse Signature from base16 encoded string.

Signing

sign Source #

Arguments

:: ToCBOR a 
=> ProtocolMagicId 
-> SignTag

See docs for SignTag

-> SigningKey 
-> a 
-> Signature a 

Encode something with ToCBOR and sign it

signEncoded :: ProtocolMagicId -> SignTag -> SigningKey -> Encoding -> Signature a Source #

Like sign but without the ToCBOR constraint

signRaw Source #

Arguments

:: ProtocolMagicId 
-> Maybe SignTag

See docs for SignTag. Unlike in sign, we allow no tag to be provided just in case you need to sign exactly the bytestring you provided.

-> SigningKey 
-> ByteString 
-> Signature Raw 

Sign a Raw bytestring

Verification

verifySignature :: (a -> Encoding) -> ProtocolMagicId -> SignTag -> VerificationKey -> a -> Signature a -> Bool Source #

Verify a signature

toVerification :: SigningKey -> VerificationKey Source #

Generate a verification key from a signing key. Fast (it just drops some bytes off the signing key).

newtype VerificationKey Source #

Wrapper around XPub.

Constructors

VerificationKey 

Instances

Instances details
Eq VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Ord VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Show VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Generic VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Associated Types

type Rep VerificationKey :: Type -> Type #

ToJSON VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

FromJSON VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

ToCBOR VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

FromCBOR VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

NFData VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Methods

rnf :: VerificationKey -> () #

Buildable VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

NoThunks VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Monad m => ToJSON m VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

MonadError SchemaError m => FromJSON m VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

type Rep VerificationKey Source # 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

type Rep VerificationKey = D1 ('MetaData "VerificationKey" "Cardano.Crypto.Signing.VerificationKey" "cardano-crypto-wrapper-1.3.0-6xpOK9u3M8m70P8UdE8hNf" 'True) (C1 ('MetaCons "VerificationKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVerificationKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XPub)))

fullVerificationKeyF :: Format r (VerificationKey -> r) Source #

Formatter for VerificationKey to show it in base64.

fullVerificationKeyHexF :: Format r (VerificationKey -> r) Source #

Formatter for VerificationKey to show it in hex.

shortVerificationKeyHexF :: Format r (VerificationKey -> r) Source #

Formatter for VerificationKey to show it in hex, but only first 8 chars.

parseFullVerificationKey :: Text -> Either VerificationKeyParseError VerificationKey Source #

Parse VerificationKey from base64 encoded string

keyGen :: MonadRandom m => m (VerificationKey, SigningKey) Source #

Generate a key pair. It's recommended to run it with runSecureRandom from Cardano.Crypto.Random because the OpenSSL generator is probably safer than the default IO generator.

deterministicKeyGen :: ByteString -> (VerificationKey, SigningKey) Source #

Create key pair deterministically from 32 bytes.