cryptonite-0.30: Cryptography Primitives sink
LicenseBSD-style
MaintainerOlivier Chéron <olivier.cheron@gmail.com>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Crypto.PubKey.EdDSA

Description

EdDSA signature generation and verification, implemented in Haskell and parameterized with elliptic curve and hash algorithm. Only edwards25519 is supported at the moment.

The module provides "context" and "prehash" variants defined in RFC 8032.

This implementation is most useful when wanting to customize the hash algorithm. See module Crypto.PubKey.Ed25519 for faster Ed25519 with SHA-512.

Synopsis

Documentation

data SecretKey curve Source #

An EdDSA Secret key

Instances

Instances details
Eq (SecretKey curve) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

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

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

Show (SecretKey curve) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

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

show :: SecretKey curve -> String #

showList :: [SecretKey curve] -> ShowS #

NFData (SecretKey curve) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

rnf :: SecretKey curve -> () #

ByteArrayAccess (SecretKey curve) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

length :: SecretKey curve -> Int #

withByteArray :: SecretKey curve -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: SecretKey curve -> Ptr p -> IO () #

data PublicKey curve hash Source #

An EdDSA public key

Instances

Instances details
Eq (PublicKey curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

(==) :: PublicKey curve hash -> PublicKey curve hash -> Bool #

(/=) :: PublicKey curve hash -> PublicKey curve hash -> Bool #

Show (PublicKey curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

showsPrec :: Int -> PublicKey curve hash -> ShowS #

show :: PublicKey curve hash -> String #

showList :: [PublicKey curve hash] -> ShowS #

NFData (PublicKey curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

rnf :: PublicKey curve hash -> () #

ByteArrayAccess (PublicKey curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

length :: PublicKey curve hash -> Int #

withByteArray :: PublicKey curve hash -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: PublicKey curve hash -> Ptr p -> IO () #

data Signature curve hash Source #

An EdDSA signature

Instances

Instances details
Eq (Signature curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

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

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

Show (Signature curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

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

show :: Signature curve hash -> String #

showList :: [Signature curve hash] -> ShowS #

NFData (Signature curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

rnf :: Signature curve hash -> () #

ByteArrayAccess (Signature curve hash) Source # 
Instance details

Defined in Crypto.PubKey.EdDSA

Methods

length :: Signature curve hash -> Int #

withByteArray :: Signature curve hash -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Signature curve hash -> Ptr p -> IO () #

Curves with EdDSA implementation

class (EllipticCurveBasepointArith curve, KnownNat (CurveDigestSize curve)) => EllipticCurveEdDSA curve Source #

Elliptic curves with an implementation of EdDSA

Minimal complete definition

secretKeySize, hashWithDom, pointPublic, publicPoint, encodeScalarLE, decodeScalarLE, scheduleSecret

Associated Types

type CurveDigestSize curve :: Nat Source #

Size of the digest for this curve (in bytes)

publicKeySize :: EllipticCurveEdDSA curve => proxy curve -> Int Source #

Size of public keys for this curve (in bytes)

secretKeySize :: EllipticCurveEdDSA curve => proxy curve -> Int Source #

Size of secret keys for this curve (in bytes)

signatureSize :: forall proxy curve. EllipticCurveEdDSA curve => proxy curve -> Int Source #

Size of signatures for this curve (in bytes)

Smart constructors

signature :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ba) => proxy curve -> hash -> ba -> CryptoFailable (Signature curve hash) Source #

Try to build a signature from a bytearray

publicKey :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ba) => proxy curve -> hash -> ba -> CryptoFailable (PublicKey curve hash) Source #

Try to build a public key from a bytearray

secretKey :: (EllipticCurveEdDSA curve, ByteArrayAccess ba) => proxy curve -> ba -> CryptoFailable (SecretKey curve) Source #

Try to build a secret key from a bytearray

Methods

toPublic :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve) => proxy curve -> hash -> SecretKey curve -> PublicKey curve hash Source #

Create a public key from a secret key

sign :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess msg) => proxy curve -> SecretKey curve -> PublicKey curve hash -> msg -> Signature curve hash Source #

Sign a message using the key pair

signCtx :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ctx, ByteArrayAccess msg) => proxy curve -> ctx -> SecretKey curve -> PublicKey curve hash -> msg -> Signature curve hash Source #

Sign a message using the key pair under context ctx

signPh :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ctx) => proxy curve -> ctx -> SecretKey curve -> PublicKey curve hash -> Digest prehash -> Signature curve hash Source #

Sign a prehashed message using the key pair under context ctx

verify :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess msg) => proxy curve -> PublicKey curve hash -> msg -> Signature curve hash -> Bool Source #

Verify a message

verifyCtx :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ctx, ByteArrayAccess msg) => proxy curve -> ctx -> PublicKey curve hash -> msg -> Signature curve hash -> Bool Source #

Verify a message under context ctx

verifyPh :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ctx) => proxy curve -> ctx -> PublicKey curve hash -> Digest prehash -> Signature curve hash -> Bool Source #

Verify a prehashed message under context ctx

generateSecretKey :: (EllipticCurveEdDSA curve, MonadRandom m) => proxy curve -> m (SecretKey curve) Source #

Generate a secret key