Copyright | (c) 2023 Kevin Hoffman |
---|---|
License | Apache-2.0 |
Maintainer | Kevin Hoffman |
Safe Haskell | None |
Language | Haskell2010 |
Support for the NATS encoding of ed25519 key pairs. Internally these keys and seeds are standard ed25519 bytes. This package provides an encoding/decoding layer on top that produces the long, capital-letter keys that begin with well-known prefixes.
The main benefit to using the NATS encoding for ed25519 keys is that Nkeys are URL-safe, prefixed with the purpose/role of the key, and are even double-clickable on most computers. Nkeys are also an integral part of NATS's decentralized, JWT-based security.
Usage
The following code shows some of the common ways of using this library
Creating a key pair from random bytes:
>>>
bob <- create User
>>>
bob
UBXEJQE5OZ2Y7YAWGLRQQDTFFUVUQMRZG6W4BU3FW2XDNYBXMH72OR45
Create a key pair from an existing seed:
>>>
Just alice = createFromSeed $ seed bob
>>>
alice
UBXEJQE5OZ2Y7YAWGLRQQDTFFUVUQMRZG6W4BU3FW2XDNYBXMH72OR45
Sign and verify messages using keys:
>>>
let message = C.pack "hello there"
>>>
let Just sig = sign bob message
>>>
let verified = verify bob message sig
Synopsis
- create :: KeyPrefix -> IO KeyPair
- sign :: KeyPair -> ByteString -> Maybe Signature
- verify :: KeyPair -> ByteString -> Signature -> Bool
- data KeyPair
- publicKey :: KeyPair -> ByteString
- seed :: KeyPair -> ByteString
- createFromSeed :: ByteString -> Maybe KeyPair
- data KeyPrefix
- data Signature
Documentation
create :: KeyPrefix -> IO KeyPair Source #
This IO action creates a new key pair from a randomly generated 32-byte seed
sign :: KeyPair -> ByteString -> Maybe Signature Source #
Signs the given input bytes using the key pair's seed key
verify :: KeyPair -> ByteString -> Signature -> Bool Source #
Verifies a signature against the key pair's public key and the input bytes
Represents an ed25519 key pair with NATS string encoding
publicKey :: KeyPair -> ByteString Source #
Returns the public key of the pair as a prefixed byte string
seed :: KeyPair -> ByteString Source #
Returns the seed (private) key of the pair as a prefixed string starting with S
createFromSeed :: ByteString -> Maybe KeyPair Source #
Creates a new keypair from an encoded seed with an appropriate prefix. Do not call this function with unencoded ed25519 seeds
Represents the well-known prefixes available for NATS-encoded keys
Seed | (S) Precedes all seed keys, followed by a type prefix |
Private | (P) Used for private keys |
Server | (N) Servers and their ilk (nodes, processes, etc) |
Cluster | (C) Clusters |
Operator | (O) Operators |
Account | (A) Accounts |
User | (U) Users |
Curve | (X) Curve keys used for encryption/decryption |
Unknown | (Z) Catch-all for unknown prefixes |
Instances
Data KeyPrefix Source # | |
Defined in Nats.Nkeys.Codec gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyPrefix -> c KeyPrefix # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeyPrefix # toConstr :: KeyPrefix -> Constr # dataTypeOf :: KeyPrefix -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KeyPrefix) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyPrefix) # gmapT :: (forall b. Data b => b -> b) -> KeyPrefix -> KeyPrefix # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyPrefix -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyPrefix -> r # gmapQ :: (forall d. Data d => d -> u) -> KeyPrefix -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyPrefix -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyPrefix -> m KeyPrefix # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyPrefix -> m KeyPrefix # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyPrefix -> m KeyPrefix # | |
Show KeyPrefix Source # | |
Eq KeyPrefix Source # | |
A
which is detached from the message it signed.Signature
Since: ed25519-0.0.1.0
Instances
Generic Signature | |||||
Defined in Crypto.Sign.Ed25519
| |||||
Show Signature | |||||
Eq Signature | |||||
Ord Signature | |||||
Defined in Crypto.Sign.Ed25519 | |||||
type Rep Signature | |||||
Defined in Crypto.Sign.Ed25519 type Rep Signature = D1 ('MetaData "Signature" "Crypto.Sign.Ed25519" "d25519-0.0.5.0-23667800" 'True) (C1 ('MetaCons "Signature" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |