License | BSD-style |
---|---|
Maintainer | Olivier Chéron <olivier.cheron@gmail.com> |
Stability | experimental |
Portability | unknown |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- data SecretKey curve
- data PublicKey curve hash
- data Signature curve hash
- class (EllipticCurveBasepointArith curve, KnownNat (CurveDigestSize curve)) => EllipticCurveEdDSA curve where
- type CurveDigestSize curve :: Nat
- publicKeySize :: EllipticCurveEdDSA curve => proxy curve -> Int
- secretKeySize :: EllipticCurveEdDSA curve => proxy curve -> Int
- signatureSize :: forall proxy curve. EllipticCurveEdDSA curve => proxy curve -> Int
- signature :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ba) => proxy curve -> hash -> ba -> CryptoFailable (Signature curve hash)
- publicKey :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ba) => proxy curve -> hash -> ba -> CryptoFailable (PublicKey curve hash)
- secretKey :: (EllipticCurveEdDSA curve, ByteArrayAccess ba) => proxy curve -> ba -> CryptoFailable (SecretKey curve)
- toPublic :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve) => proxy curve -> hash -> SecretKey curve -> PublicKey curve hash
- sign :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess msg) => proxy curve -> SecretKey curve -> PublicKey curve hash -> msg -> Signature curve hash
- 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
- signPh :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ctx) => proxy curve -> ctx -> SecretKey curve -> PublicKey curve hash -> Digest prehash -> Signature curve hash
- verify :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess msg) => proxy curve -> PublicKey curve hash -> msg -> Signature curve hash -> Bool
- verifyCtx :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ctx, ByteArrayAccess msg) => proxy curve -> ctx -> PublicKey curve hash -> msg -> Signature curve hash -> Bool
- verifyPh :: (EllipticCurveEdDSA curve, HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize curve, ByteArrayAccess ctx) => proxy curve -> ctx -> PublicKey curve hash -> Digest prehash -> Signature curve hash -> Bool
- generateSecretKey :: (EllipticCurveEdDSA curve, MonadRandom m) => proxy curve -> m (SecretKey curve)
Documentation
An EdDSA Secret key
data PublicKey curve hash Source #
An EdDSA public key
data Signature curve hash Source #
An EdDSA signature
Curves with EdDSA implementation
class (EllipticCurveBasepointArith curve, KnownNat (CurveDigestSize curve)) => EllipticCurveEdDSA curve Source #
Elliptic curves with an implementation of EdDSA
secretKeySize, hashWithDom, pointPublic, publicPoint, encodeScalarLE, decodeScalarLE, scheduleSecret
type CurveDigestSize curve :: Nat Source #
Size of the digest for this curve (in bytes)
Instances
EllipticCurveEdDSA Curve_Edwards25519 Source # | |
Defined in Crypto.PubKey.EdDSA type CurveDigestSize Curve_Edwards25519 :: Nat Source # secretKeySize :: proxy Curve_Edwards25519 -> Int Source # hashWithDom :: (HashAlgorithm hash, ByteArrayAccess ctx, ByteArrayAccess msg) => proxy Curve_Edwards25519 -> hash -> Bool -> ctx -> Builder -> msg -> Bytes pointPublic :: proxy Curve_Edwards25519 -> Point Curve_Edwards25519 -> PublicKey Curve_Edwards25519 hash publicPoint :: proxy Curve_Edwards25519 -> PublicKey Curve_Edwards25519 hash -> CryptoFailable (Point Curve_Edwards25519) encodeScalarLE :: ByteArray bs => proxy Curve_Edwards25519 -> Scalar Curve_Edwards25519 -> bs decodeScalarLE :: ByteArrayAccess bs => proxy Curve_Edwards25519 -> bs -> CryptoFailable (Scalar Curve_Edwards25519) scheduleSecret :: (HashAlgorithm hash, HashDigestSize hash ~ CurveDigestSize Curve_Edwards25519) => proxy Curve_Edwards25519 -> hash -> SecretKey Curve_Edwards25519 -> (Scalar Curve_Edwards25519, View 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