Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Crypto.Paseto.Keys.V3
Description
P384 ECDSA cryptographic keys.
Synopsis
- curveP384 :: Curve
- data PrivateKeyP384 where
- pattern PrivateKeyP384 :: PrivateKey -> PrivateKeyP384
- unPrivateKeyP384 :: PrivateKeyP384 -> PrivateKey
- mkPrivateKeyP384 :: PrivateKey -> Maybe PrivateKeyP384
- generatePrivateKeyP384 :: IO PrivateKeyP384
- encodePrivateKeyP384 :: PrivateKeyP384 -> ScrubbedBytes
- data ScalarDecodingError
- renderScalarDecodingError :: ScalarDecodingError -> Text
- decodePrivateKeyP384 :: ScrubbedBytes -> Either ScalarDecodingError PrivateKeyP384
- generateScalarP384 :: IO Integer
- isScalarValidP384 :: Integer -> Bool
- data PublicKeyP384 where
- pattern PublicKeyP384 :: PublicKey -> PublicKeyP384
- unPublicKeyP384 :: PublicKeyP384 -> PublicKey
- mkPublicKeyP384 :: PublicKey -> Maybe PublicKeyP384
- fromPrivateKeyP384 :: PrivateKeyP384 -> PublicKeyP384
- encodePublicKeyP384 :: PublicKeyP384 -> ByteString
- data CompressedPointDecodingError
- data UncompressedPointDecodingError
- data PublicKeyP384DecodingError
- renderPublicKeyP384DecodingError :: PublicKeyP384DecodingError -> Text
- decodePublicKeyP384 :: ByteString -> Either PublicKeyP384DecodingError PublicKeyP384
Curve
Elliptic curve SEC_p384r1
.
Private key
data PrivateKeyP384 where Source #
ECDSA private key for curve SEC_p384r1
.
Note that this type's Eq
instance performs a constant-time equality
check.
Bundled Patterns
pattern PrivateKeyP384 :: PrivateKey -> PrivateKeyP384 |
Instances
Show PrivateKeyP384 Source # | |
Defined in Crypto.Paseto.Keys.V3 Methods showsPrec :: Int -> PrivateKeyP384 -> ShowS # show :: PrivateKeyP384 -> String # showList :: [PrivateKeyP384] -> ShowS # | |
Eq PrivateKeyP384 Source # | |
Defined in Crypto.Paseto.Keys.V3 Methods (==) :: PrivateKeyP384 -> PrivateKeyP384 -> Bool # (/=) :: PrivateKeyP384 -> PrivateKeyP384 -> Bool # |
mkPrivateKeyP384 :: PrivateKey -> Maybe PrivateKeyP384 Source #
Construct a private key for curve SEC_p384r1
.
generatePrivateKeyP384 :: IO PrivateKeyP384 Source #
Generate a private key for curve SEC_p384r1
.
data ScalarDecodingError Source #
Error decoding a scalar value.
Constructors
ScalarDecodingInvalidLengthError | Invalid scalar length. |
ScalarDecodingInvalidError | Decoded scalar is invalid for the curve. |
Instances
Show ScalarDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal Methods showsPrec :: Int -> ScalarDecodingError -> ShowS # show :: ScalarDecodingError -> String # showList :: [ScalarDecodingError] -> ShowS # | |
Eq ScalarDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal Methods (==) :: ScalarDecodingError -> ScalarDecodingError -> Bool # (/=) :: ScalarDecodingError -> ScalarDecodingError -> Bool # |
renderScalarDecodingError :: ScalarDecodingError -> Text Source #
Render a ScalarDecodingError
as Text
.
Helpers
generateScalarP384 :: IO Integer Source #
Generate a random scalar on the curve SEC_p384r1
.
isScalarValidP384 :: Integer -> Bool Source #
Whether a scalar is valid on the curve SEC_p384r1
.
Public key
data PublicKeyP384 where Source #
ECDSA public key for curve SEC_p384r1
.
Bundled Patterns
pattern PublicKeyP384 :: PublicKey -> PublicKeyP384 |
Instances
Show PublicKeyP384 Source # | |
Defined in Crypto.Paseto.Keys.V3 Methods showsPrec :: Int -> PublicKeyP384 -> ShowS # show :: PublicKeyP384 -> String # showList :: [PublicKeyP384] -> ShowS # | |
Eq PublicKeyP384 Source # | |
Defined in Crypto.Paseto.Keys.V3 Methods (==) :: PublicKeyP384 -> PublicKeyP384 -> Bool # (/=) :: PublicKeyP384 -> PublicKeyP384 -> Bool # |
mkPublicKeyP384 :: PublicKey -> Maybe PublicKeyP384 Source #
Construct a public key for curve SEC_p384r1
.
fromPrivateKeyP384 :: PrivateKeyP384 -> PublicKeyP384 Source #
Construct the PublicKeyP384
which corresponds to a given
PrivateKeyP384
.
encodePublicKeyP384 :: PublicKeyP384 -> ByteString Source #
Encode an elliptic curve point into its compressed binary format as defined by SEC 1 and RFC 5480 section 2.2.
data CompressedPointDecodingError Source #
Error decoding a compressed elliptic curve point.
Constructors
CompressedPointDecodingInvalidPrefixError | Prefix is not either of the expected values ( |
Fields
| |
CompressedPointDecodingInvalidLengthError | Length of the provided compressed point is invalid. |
CompressedPointDecodingModularSquareRootError | Failed to find the modular square root of a value. |
CompressedPointDecodingInvalidPointError !Point | Point is invalid for the curve. |
Instances
Show CompressedPointDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal Methods showsPrec :: Int -> CompressedPointDecodingError -> ShowS # show :: CompressedPointDecodingError -> String # showList :: [CompressedPointDecodingError] -> ShowS # | |
Eq CompressedPointDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal Methods (==) :: CompressedPointDecodingError -> CompressedPointDecodingError -> Bool # (/=) :: CompressedPointDecodingError -> CompressedPointDecodingError -> Bool # |
data UncompressedPointDecodingError Source #
Error decoding an uncompressed elliptic curve point.
Constructors
UncompressedPointDecodingInvalidPrefixError | Prefix is not the expected value ( |
Fields
| |
UncompressedPointDecodingInvalidLengthError | Length of the provided point is invalid. |
UncompressedPointDecodingInvalidPointError !Point | Point is invalid for the curve. |
Instances
Show UncompressedPointDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal Methods showsPrec :: Int -> UncompressedPointDecodingError -> ShowS # show :: UncompressedPointDecodingError -> String # showList :: [UncompressedPointDecodingError] -> ShowS # | |
Eq UncompressedPointDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal |
data PublicKeyP384DecodingError Source #
Error decoding a public key for curve SEC_p384r1
.
Constructors
PublicKeyP384DecodingCompressedError !CompressedPointDecodingError | Error decoding a compressed public key. |
PublicKeyP384DecodingUncompressedError !UncompressedPointDecodingError | Error decoding an uncompressed public key. |
Instances
Show PublicKeyP384DecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3 Methods showsPrec :: Int -> PublicKeyP384DecodingError -> ShowS # show :: PublicKeyP384DecodingError -> String # showList :: [PublicKeyP384DecodingError] -> ShowS # | |
Eq PublicKeyP384DecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3 Methods (==) :: PublicKeyP384DecodingError -> PublicKeyP384DecodingError -> Bool # (/=) :: PublicKeyP384DecodingError -> PublicKeyP384DecodingError -> Bool # |
renderPublicKeyP384DecodingError :: PublicKeyP384DecodingError -> Text Source #
Render a PublicKeyP384DecodingError
as Text
.
decodePublicKeyP384 :: ByteString -> Either PublicKeyP384DecodingError PublicKeyP384 Source #
Decode a public key from either its compressed or uncompressed binary format as defined by SEC 1 and RFC 5480 section 2.2.