cryptonite-0.27: Cryptography Primitives sink

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Crypto.PubKey.ECDSA

Contents

Description

Elliptic Curve Digital Signature Algorithm, with the parameterized curve implementations provided by module Crypto.ECC.

Public/private key pairs can be generated using curveGenerateKeyPair or decoded from binary.

WARNING: Only curve P-256 has constant-time implementation. Signature operations with P-384 and P-521 may leak the private key.

Signature verification should be safe for all curves.

Synopsis

Documentation

class EllipticCurveBasepointArith curve => EllipticCurveECDSA curve where Source #

Elliptic curves with ECDSA capabilities.

Minimal complete definition

scalarIsValid, scalarInv, pointX

Methods

scalarIsValid :: proxy curve -> Scalar curve -> Bool Source #

Is a scalar in the accepted range for ECDSA

scalarIsZero :: proxy curve -> Scalar curve -> Bool Source #

Test whether the scalar is zero

scalarInv :: proxy curve -> Scalar curve -> Maybe (Scalar curve) Source #

Scalar inversion modulo the curve order

pointX :: proxy curve -> Point curve -> Maybe (Scalar curve) Source #

Return the point X coordinate as a scalar

Public keys

type PublicKey curve = Point curve Source #

ECDSA Public Key.

encodePublic :: (EllipticCurve curve, ByteArray bs) => proxy curve -> PublicKey curve -> bs Source #

Encode a public key into binary form, i.e. the uncompressed encoding referenced from RFC 5480 section 2.2.

decodePublic :: (EllipticCurve curve, ByteArray bs) => proxy curve -> bs -> CryptoFailable (PublicKey curve) Source #

Try to decode the binary form of a public key.

toPublic :: EllipticCurveECDSA curve => proxy curve -> PrivateKey curve -> PublicKey curve Source #

Create a public key from a private key.

Private keys

type PrivateKey curve = Scalar curve Source #

ECDSA Private Key.

encodePrivate :: (EllipticCurveECDSA curve, ByteArray bs) => proxy curve -> PrivateKey curve -> bs Source #

Encode a private key into binary form, i.e. the privateKey field described in RFC 5915.

decodePrivate :: (EllipticCurveECDSA curve, ByteArray bs) => proxy curve -> bs -> CryptoFailable (PrivateKey curve) Source #

Try to decode the binary form of a private key.

Signatures

data Signature curve Source #

Represent a ECDSA signature namely R and S.

Constructors

Signature 

Fields

Instances
Eq (Scalar curve) => Eq (Signature curve) Source # 
Instance details

Defined in Crypto.PubKey.ECDSA

Methods

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

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

Show (Scalar curve) => Show (Signature curve) Source # 
Instance details

Defined in Crypto.PubKey.ECDSA

Methods

showsPrec :: Int -> Signature curve -> ShowS #

show :: Signature curve -> String #

showList :: [Signature curve] -> ShowS #

NFData (Scalar curve) => NFData (Signature curve) Source # 
Instance details

Defined in Crypto.PubKey.ECDSA

Methods

rnf :: Signature curve -> () #

signatureFromIntegers :: EllipticCurveECDSA curve => proxy curve -> (Integer, Integer) -> CryptoFailable (Signature curve) Source #

Create a signature from integers (R, S).

signatureToIntegers :: EllipticCurveECDSA curve => proxy curve -> Signature curve -> (Integer, Integer) Source #

Get integers (R, S) from a signature.

The values can then be used to encode the signature to binary with ASN.1.

Generation and verification

signWith :: (EllipticCurveECDSA curve, ByteArrayAccess msg, HashAlgorithm hash) => proxy curve -> Scalar curve -> PrivateKey curve -> hash -> msg -> Maybe (Signature curve) Source #

Sign message using the private key and an explicit k scalar.

signDigestWith :: (EllipticCurveECDSA curve, HashAlgorithm hash) => proxy curve -> Scalar curve -> PrivateKey curve -> Digest hash -> Maybe (Signature curve) Source #

Sign digest using the private key and an explicit k scalar.

sign :: (EllipticCurveECDSA curve, MonadRandom m, ByteArrayAccess msg, HashAlgorithm hash) => proxy curve -> PrivateKey curve -> hash -> msg -> m (Signature curve) Source #

Sign a message using hash and private key.

signDigest :: (EllipticCurveECDSA curve, MonadRandom m, HashAlgorithm hash) => proxy curve -> PrivateKey curve -> Digest hash -> m (Signature curve) Source #

Sign a digest using hash and private key.

verify :: (EllipticCurveECDSA curve, ByteArrayAccess msg, HashAlgorithm hash) => proxy curve -> hash -> PublicKey curve -> Signature curve -> msg -> Bool Source #

Verify a signature using hash and public key.

verifyDigest :: (EllipticCurveECDSA curve, HashAlgorithm hash) => proxy curve -> PublicKey curve -> Signature curve -> Digest hash -> Bool Source #

Verify a digest using hash and public key.